163 SUBROUTINE dlaed1( N, D, Q, LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK,
172 INTEGER CUTPNT, INFO, LDQ, N
176 INTEGER INDXQ( * ), IWORK( * )
177 DOUBLE PRECISION D( * ), Q( ldq, * ), WORK( * )
183 INTEGER COLTYP, I, IDLMDA, INDX, INDXC, INDXP, IQ2, IS,
184 $ iw, iz, k, n1, n2, zpp1
200 ELSE IF( ldq.LT.max( 1, n ) )
THEN
202 ELSE IF( min( 1, n / 2 ).GT.cutpnt .OR. ( n / 2 ).LT.cutpnt )
THEN
206 CALL xerbla(
'DLAED1', -info )
233 CALL dcopy( cutpnt, q( cutpnt, 1 ), ldq, work( iz ), 1 )
235 CALL dcopy( n-cutpnt, q( zpp1, zpp1 ), ldq, work( iz+cutpnt ), 1 )
239 CALL dlaed2( k, n, cutpnt, d, q, ldq, indxq, rho, work( iz ),
240 $ work( idlmda ), work( iw ), work( iq2 ),
241 $ iwork( indx ), iwork( indxc ), iwork( indxp ),
242 $ iwork( coltyp ), info )
250 is = ( iwork( coltyp )+iwork( coltyp+1 ) )*cutpnt +
251 $ ( iwork( coltyp+1 )+iwork( coltyp+2 ) )*( n-cutpnt ) + iq2
252 CALL dlaed3( k, n, cutpnt, d, q, ldq, rho, work( idlmda ),
253 $ work( iq2 ), iwork( indxc ), iwork( coltyp ),
254 $ work( iw ), work( is ), info )
262 CALL dlamrg( n1, n2, d, 1, -1, indxq )
subroutine dcopy(N, DX, INCX, DY, INCY)
DCOPY
subroutine dlaed3(K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT, W, S, INFO)
DLAED3 used by sstedc. Finds the roots of the secular equation and updates the eigenvectors. Used when the original matrix is tridiagonal.
subroutine dlaed1(N, D, Q, LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK, INFO)
DLAED1 used by sstedc. Computes the updated eigensystem of a diagonal matrix after modification by a ...
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...
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine dlaed2(K, N, N1, D, Q, LDQ, INDXQ, RHO, Z, DLAMDA, W, Q2, INDX, INDXC, INDXP, COLTYP, INFO)
DLAED2 used by sstedc. Merges eigenvalues and deflates secular equation. Used when the original matri...