131 SUBROUTINE zsteqr( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
142 DOUBLE PRECISION D( * ), E( * ), WORK( * )
143 COMPLEX*16 Z( LDZ, * )
149 DOUBLE PRECISION , ONE, TWO, THREE
150 parameter( zero = 0.0d0, one = 1.0d0, two = 2.0d0,
152 COMPLEX*16 CZERO, CONE
153 parameter( czero = ( 0.0d0, 0.0d0 ),
154 $ cone = ( 1.0d0, 0.0d0 ) )
156 parameter( maxit = 30 )
159 INTEGER I, ICOMPZ, II, ISCALE, J, JTOT, K, L, L1, LEND,
160 $ LENDM1, LENDP1, LENDSV, LM1, LSV, M, MM, MM1,
162 DOUBLE PRECISION ANORM, B, C, EPS, EPS2, F, G, P, R, RT1, RT2,
163 $ S, SAFMAX, SAFMIN, SSFMAX, SSFMIN, TST
167 DOUBLE PRECISION DLAMCH, DLANST, DLAPY2
168 EXTERNAL lsame, dlamch, dlanst, dlapy2
175 INTRINSIC abs,
max, sign, sqrt
183 IF( lsame( compz,
'N' ) )
THEN
185 ELSE IF( lsame( compz,
'V' ) )
THEN
187 ELSE IF( lsame( compz, 'i
' ) ) THEN
192.LT.
IF( ICOMPZ0 ) THEN
194.LT.
ELSE IF( N0 ) THEN
196.LT..OR..GT..AND..LT.
ELSE IF( ( LDZ1 ) ( ICOMPZ0 LDZMAX( 1,
201 CALL XERBLA( 'zsteqr', -INFO )
220 SAFMIN = DLAMCH( 's
' )
221 SAFMAX = ONE / SAFMIN
222 SSFMAX = SQRT( SAFMAX ) / THREE
223 SSFMIN = SQRT( SAFMIN ) / EPS2
229 $ CALL ZLASET( 'full
', N, N, CZERO, CONE, Z, LDZ )
251.LE.
IF( TST( SQRT( ABS( D( M ) ) )*SQRT( ABS( D( M+
252 $ 1 ) ) ) )*EPS ) THEN
271 ANORM = DLANST( 'i
', LEND-L+1, D( L ), E( L ) )
275.GT.
IF( ANORMSSFMAX ) THEN
277 CALL DLASCL( 'g
', 0, 0, ANORM, SSFMAX, LEND-L+1, 1, D( L ), N,
279 CALL DLASCL( 'g
', 0, 0, ANORM, SSFMAX, LEND-L, 1, E( L ), N,
281.LT.
ELSE IF( ANORMSSFMIN ) THEN
283 CALL DLASCL( 'g
', 0, 0, ANORM, SSFMIN, LEND-L+1, 1, D( L ), N,
285 CALL DLASCL( 'g
', 0, 0, ANORM, SSFMIN, LEND-L, 1, E( L ), N,
291.LT.
IF( ABS( D( LEND ) )ABS( D( L ) ) ) THEN
306 TST = ABS( E( M ) )**2
307.LE.
IF( TST( EPS2*ABS( D( M ) ) )*ABS( D( M+1 ) )+
325.GT.
IF( ICOMPZ0 ) THEN
326 CALL DLAEV2( D( L ), E( L ), D( L+1 ), RT1, RT2, C, S )
329 CALL ZLASR( 'r
', 'v
', 'b
', N, 2, WORK( L ),
330 $ WORK( N-1+L ), Z( 1, L ), LDZ )
332 CALL DLAE2( D( L ), E( L ), D( L+1 ), RT1, RT2 )
349 G = ( D( L+1 )-P ) / ( TWO*E( L ) )
351 G = D( M ) - P + ( E( L ) / ( G+SIGN( R, G ) ) )
363 CALL DLARTG( G, F, C, S, R )
367 R = ( D( I )-G )*S + TWO*C*B
374.GT.
IF( ICOMPZ0 ) THEN
383.GT.
IF( ICOMPZ0 ) THEN
385 CALL ZLASR( 'r
', 'v
', 'b
', N, MM, WORK( L ), WORK( N-1+L ),
412 DO 100 M = L, LENDP1, -1
413 TST = ABS( E( M-1 ) )**2
414.LE.
IF( TST( EPS2*ABS( D( M ) ) )*ABS( D( M-1 ) )+
432.GT.
IF( ICOMPZ0 ) THEN
433 CALL DLAEV2( D( L-1 ), E( L-1 ), D( L ), RT1, RT2, C, S )
436 CALL ZLASR( 'r
', 'v
', 'f
', N, 2, WORK( M ),
437 $ WORK( N-1+M ), Z( 1, L-1 ), LDZ )
439 CALL DLAE2( D( L-1 ), E( L-1 ), D( L ), RT1, RT2 )
456 G = ( D( L-1 )-P ) / ( TWO*E( L-1 ) )
458 G = D( M ) - P + ( E( L-1 ) / ( G+SIGN( R, G ) ) )
470 CALL DLARTG( G, F, C, S, R )
474 R = ( D( I+1 )-G )*S + TWO*C*B
481.GT.
IF( ICOMPZ0 ) THEN
490.GT.
IF( ICOMPZ0 ) THEN
492 CALL ZLASR( 'r
', 'v
', 'f
', N, MM, WORK( M ), WORK( N-1+M ),
515.EQ.
IF( ISCALE1 ) THEN
516 CALL DLASCL( 'g
', 0, 0, SSFMAX, ANORM, LENDSV-LSV+1, 1,
517 $ D( LSV ), N, INFO )
518 CALL DLASCL( 'g
', 0, 0, SSFMAX, ANORM, LENDSV-LSV, 1, E( LSV ),
520.EQ.
ELSE IF( ISCALE2 ) THEN
521 CALL DLASCL( 'g
', 0, 0, SSFMIN, ANORM, LENDSV-LSV+1, 1,
522 $ D( LSV ), N, INFO )
523 CALL DLASCL( 'g
', 0, 0, SSFMIN, ANORM, LENDSV-LSV, 1, E( LSV ),
530.EQ.
IF( JTOTNMAXIT ) THEN
542.EQ.
IF( ICOMPZ0 ) THEN
546 CALL DLASRT( 'i
', N, D, INFO )
557.LT.
IF( D( J )P ) THEN
565 CALL ZSWAP( N, Z( 1, I ), 1, Z( 1, K ), 1 )
subroutine dlae2(a, b, c, rt1, rt2)
DLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix.
subroutine dlartg(f, g, c, s, r)
DLARTG generates a plane rotation with real cosine and real sine.
subroutine dlaev2(a, b, c, rt1, rt2, cs1, sn1)
DLAEV2 computes the eigenvalues and eigenvectors of a 2-by-2 symmetric/Hermitian matrix.
subroutine dlascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
DLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
subroutine dlasrt(id, n, d, info)
DLASRT sorts numbers in increasing or decreasing order.
subroutine xerbla(srname, info)
XERBLA
subroutine zlasr(side, pivot, direct, m, n, c, s, a, lda)
ZLASR applies a sequence of plane rotations to a general rectangular matrix.
subroutine zlaset(uplo, m, n, alpha, beta, a, lda)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine zsteqr(compz, n, d, e, z, ldz, work, info)
ZSTEQR
subroutine zswap(n, zx, incx, zy, incy)
ZSWAP