173 SUBROUTINE slaed3( K, N, N1, D, Q, LDQ, RHO, DLAMBDA, Q2, INDX,
181 INTEGER INFO, K, LDQ, N, N1
185 INTEGER CTOT( * ), INDX( * )
186 REAL D( * ), DLAMBDA( * ), Q( LDQ, * ), Q2( * ),
194 parameter( one = 1.0e0, zero = 0.0e0 )
197 INTEGER I, II, IQ2, J, N12, N2, N23
209 INTRINSIC max, sign, sqrt
219 ELSE IF( n.LT.k )
THEN
221 ELSE IF( ldq.LT.max( 1, n ) )
THEN
225 CALL xerbla(
'SLAED3', -info )
235 CALL slaed4( k, j, dlambda, w, q( 1, j ), rho, d( j ),
260 CALL scopy( k, w, 1, s, 1 )
264 CALL scopy( k, q, ldq+1, w, 1 )
267 w( i ) = w( i )*( q( i, j )/( dlambda( i )-dlambda( j ) ) )
270 w( i ) = w( i )*( q( i, j )/( dlambda( i )-dlambda( j ) ) )
274 w( i ) = sign( sqrt( -w( i ) ), s( i ) )
281 s( i ) = w( i ) / q( i, j )
283 temp = snrm2( k, s, 1 )
286 q( i, j ) = s( ii ) / temp
295 n12 = ctot( 1 ) + ctot( 2 )
296 n23 = ctot( 2 ) + ctot( 3 )
298 CALL slacpy(
'A', n23, k, q( ctot( 1 )+1, 1 ), ldq, s, n23 )
301 CALL sgemm(
'N',
'N', n2, k, n23, one, q2( iq2 ), n2, s,
303 $ zero, q( n1+1, 1 ), ldq )
305 CALL slaset(
'A', n2, k, zero, zero, q( n1+1, 1 ), ldq )
308 CALL slacpy(
'A', n12, k, q, ldq, s, n12 )
310 CALL sgemm(
'N',
'N', n1, k, n12, one, q2, n1, s, n12, zero,
314 CALL slaset(
'A', n1, k, zero, zero, q( 1, 1 ), ldq )
subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SGEMM
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine slaed3(k, n, n1, d, q, ldq, rho, dlambda, q2, indx, ctot, w, s, info)
SLAED3 used by SSTEDC. Finds the roots of the secular equation and updates the eigenvectors....
subroutine slaed4(n, i, d, z, delta, rho, dlam, info)
SLAED4 used by SSTEDC. Finds a single root of the secular equation.
subroutine slaset(uplo, m, n, alpha, beta, a, lda)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.