161 SUBROUTINE dlaed1( N, D, Q, LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK,
169 INTEGER CUTPNT, INFO, LDQ, N
173 INTEGER INDXQ( * ), IWORK( * )
174 DOUBLE PRECISION D( * ), Q( LDQ, * ), WORK( * )
180 INTEGER COLTYP, I, IDLMDA, INDX, INDXC, INDXP, IQ2, IS,
181 $ iw, iz, k, n1, n2, zpp1
197 ELSE IF( ldq.LT.max( 1, n ) )
THEN
199 ELSE IF( min( 1, n / 2 ).GT.cutpnt .OR. ( n / 2 ).LT.cutpnt )
THEN
203 CALL xerbla(
'DLAED1', -info )
230 CALL dcopy( cutpnt, q( cutpnt, 1 ), ldq, work( iz ), 1 )
232 CALL dcopy( n-cutpnt, q( zpp1, zpp1 ), ldq, work( iz+cutpnt ), 1 )
236 CALL dlaed2( k, n, cutpnt, d, q, ldq, indxq, rho, work( iz ),
237 $ work( idlmda ), work( iw ), work( iq2 ),
238 $ iwork( indx ), iwork( indxc ), iwork( indxp ),
239 $ iwork( coltyp ), info )
247 is = ( iwork( coltyp )+iwork( coltyp+1 ) )*cutpnt +
248 $ ( iwork( coltyp+1 )+iwork( coltyp+2 ) )*( n-cutpnt ) + iq2
249 CALL dlaed3( k, n, cutpnt, d, q, ldq, rho, work( idlmda ),
250 $ work( iq2 ), iwork( indxc ), iwork( coltyp ),
251 $ work( iw ), work( is ), info )
259 CALL dlamrg( n1, n2, d, 1, -1, indxq )
subroutine xerbla(srname, info)
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine dlaed1(n, d, q, ldq, indxq, rho, cutpnt, work, iwork, info)
DLAED1 used by DSTEDC. Computes the updated eigensystem of a diagonal matrix after modification by a ...
subroutine dlaed2(k, n, n1, d, q, ldq, indxq, rho, z, dlambda, w, q2, indx, indxc, indxp, coltyp, info)
DLAED2 used by DSTEDC. Merges eigenvalues and deflates secular equation. Used when the original matri...
subroutine dlaed3(k, n, n1, d, q, ldq, rho, dlambda, q2, indx, ctot, w, s, info)
DLAED3 used by DSTEDC. Finds the roots of the secular equation and updates the eigenvectors....
subroutine dlamrg(n1, n2, a, dtrd1, dtrd2, index)
DLAMRG creates a permutation list to merge the entries of two independently sorted sets into a single...