3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZSTEQR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zsteqr.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zsteqr.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsteqr.f">
21 * SUBROUTINE ZSTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDZ, N
27 * .. Array Arguments ..
28 * DOUBLE PRECISION D( * ), E( * ), WORK( * )
29 * COMPLEX*16 Z( LDZ, * )
38 *> ZSTEQR computes all eigenvalues and, optionally, eigenvectors of a
39 *> symmetric tridiagonal matrix using the implicit QL or QR method.
40 *> The eigenvectors of a full or band complex Hermitian matrix can also
41 *> be found if ZHETRD or ZHPTRD or ZHBTRD has been used to reduce this
42 *> matrix to tridiagonal form.
50 *> COMPZ is CHARACTER*1
51 *> = 'N': Compute eigenvalues only.
52 *> = 'V': Compute eigenvalues and eigenvectors of the original
53 *> Hermitian matrix. On entry, Z must contain the
54 *> unitary matrix used to reduce the original matrix
55 *> to tridiagonal form.
56 *> = 'I': Compute eigenvalues and eigenvectors of the
57 *> tridiagonal matrix. Z is initialized to the identity
64 *> The order of the matrix. N >= 0.
69 *> D is DOUBLE PRECISION array, dimension (N)
70 *> On entry, the diagonal elements of the tridiagonal matrix.
71 *> On exit, if INFO = 0, the eigenvalues in ascending order.
76 *> E is DOUBLE PRECISION array, dimension (N-1)
77 *> On entry, the (n-1) subdiagonal elements of the tridiagonal
79 *> On exit, E has been destroyed.
84 *> Z is COMPLEX*16 array, dimension (LDZ, N)
85 *> On entry, if COMPZ = 'V', then Z contains the unitary
86 *> matrix used in the reduction to tridiagonal form.
87 *> On exit, if INFO = 0, then if COMPZ = 'V', Z contains the
88 *> orthonormal eigenvectors of the original Hermitian matrix,
89 *> and if COMPZ = 'I', Z contains the orthonormal eigenvectors
90 *> of the symmetric tridiagonal matrix.
91 *> If COMPZ = 'N', then Z is not referenced.
97 *> The leading dimension of the array Z. LDZ >= 1, and if
98 *> eigenvectors are desired, then LDZ >= max(1,N).
103 *> WORK is DOUBLE PRECISION array, dimension (max(1,2*N-2))
104 *> If COMPZ = 'N', then WORK is not referenced.
110 *> = 0: successful exit
111 *> < 0: if INFO = -i, the i-th argument had an illegal value
112 *> > 0: the algorithm has failed to find all the eigenvalues in
113 *> a total of 30*N iterations; if INFO = i, then i
114 *> elements of E have not converged to zero; on exit, D
115 *> and E contain the elements of a symmetric tridiagonal
116 *> matrix which is unitarily similar to the original
123 *> \author Univ. of Tennessee
124 *> \author Univ. of California Berkeley
125 *> \author Univ. of Colorado Denver
128 *> \date November 2011
130 *> \ingroup complex16OTHERcomputational
132 * =====================================================================
133 SUBROUTINE ZSTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
135 * -- LAPACK computational routine (version 3.4.0) --
136 * -- LAPACK is a software package provided by Univ. of Tennessee, --
137 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
140 * .. Scalar Arguments ..
144 * .. Array Arguments ..
145 DOUBLE PRECISION D( * ), E( * ), WORK( * )
146 COMPLEX*16 Z( LDZ, * )
149 * =====================================================================
152 DOUBLE PRECISION ZERO, ONE, TWO, THREE
153 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0, TWO = 2.0D0,
155 COMPLEX*16 CZERO, CONE
156 PARAMETER ( CZERO = ( 0.0D0, 0.0D0 ),
157 $ CONE = ( 1.0D0, 0.0D0 ) )
159 PARAMETER ( MAXIT = 30 )
161 * .. Local Scalars ..
162 INTEGER I, ICOMPZ, II, ISCALE, J, JTOT, K, L, L1, LEND,
163 $ LENDM1, LENDP1, LENDSV, LM1, LSV, M, MM, MM1,
165 DOUBLE PRECISION ANORM, B, C, EPS, EPS2, F, G, P, R, RT1, RT2,
166 $ S, SAFMAX, SAFMIN, SSFMAX, SSFMIN, TST
168 * .. External Functions ..
170 DOUBLE PRECISION DLAMCH, DLANST, DLAPY2
171 EXTERNAL LSAME, DLAMCH, DLANST, DLAPY2
173 * .. External Subroutines ..
174 EXTERNAL DLAE2, DLAEV2, DLARTG, DLASCL, DLASRT, XERBLA,
175 $ ZLASET, ZLASR, ZSWAP
177 * .. Intrinsic Functions ..
178 INTRINSIC ABS, MAX, SIGN, SQRT
180 * .. Executable Statements ..
182 * Test the input parameters.
186 IF( LSAME( COMPZ, 'N' ) ) THEN
188 ELSE IF( LSAME( COMPZ, 'V' ) ) THEN
190 ELSE IF( LSAME( COMPZ, 'I' ) ) THEN
195 IF( ICOMPZ.LT.0 ) THEN
197 ELSE IF( N.LT.0 ) THEN
199 ELSE IF( ( LDZ.LT.1 ) .OR. ( ICOMPZ.GT.0 .AND. LDZ.LT.MAX( 1,
204 CALL XERBLA( 'ZSTEQR', -INFO )
208 * Quick return if possible
219 * Determine the unit roundoff and over/underflow thresholds.
223 SAFMIN = DLAMCH( 'S' )
224 SAFMAX = ONE / SAFMIN
225 SSFMAX = SQRT( SAFMAX ) / THREE
226 SSFMIN = SQRT( SAFMIN ) / EPS2
228 * Compute the eigenvalues and eigenvectors of the tridiagonal
232 $ CALL ZLASET( 'Full', N, N, CZERO, CONE, Z, LDZ )
237 * Determine where the matrix splits and choose QL or QR iteration
238 * for each block, according to whether top or bottom diagonal
239 * element is smaller.
254 IF( TST.LE.( SQRT( ABS( D( M ) ) )*SQRT( ABS( D( M+
255 $ 1 ) ) ) )*EPS ) THEN
272 * Scale submatrix in rows and columns L to LEND
274 ANORM = DLANST( 'I', LEND-L+1, D( L ), E( L ) )
278 IF( ANORM.GT.SSFMAX ) THEN
280 CALL DLASCL( 'G', 0, 0, ANORM, SSFMAX, LEND-L+1, 1, D( L ), N,
282 CALL DLASCL( 'G', 0, 0, ANORM, SSFMAX, LEND-L, 1, E( L ), N,
284 ELSE IF( ANORM.LT.SSFMIN ) THEN
286 CALL DLASCL( 'G', 0, 0, ANORM, SSFMIN, LEND-L+1, 1, D( L ), N,
288 CALL DLASCL( 'G', 0, 0, ANORM, SSFMIN, LEND-L, 1, E( L ), N,
292 * Choose between QL and QR iteration
294 IF( ABS( D( LEND ) ).LT.ABS( D( L ) ) ) THEN
303 * Look for small subdiagonal element.
309 TST = ABS( E( M ) )**2
310 IF( TST.LE.( EPS2*ABS( D( M ) ) )*ABS( D( M+1 ) )+
324 * If remaining matrix is 2-by-2, use DLAE2 or SLAEV2
325 * to compute its eigensystem.
328 IF( ICOMPZ.GT.0 ) THEN
329 CALL DLAEV2( D( L ), E( L ), D( L+1 ), RT1, RT2, C, S )
332 CALL ZLASR( 'R', 'V', 'B', N, 2, WORK( L ),
333 $ WORK( N-1+L ), Z( 1, L ), LDZ )
335 CALL DLAE2( D( L ), E( L ), D( L+1 ), RT1, RT2 )
352 G = ( D( L+1 )-P ) / ( TWO*E( L ) )
354 G = D( M ) - P + ( E( L ) / ( G+SIGN( R, G ) ) )
366 CALL DLARTG( G, F, C, S, R )
370 R = ( D( I )-G )*S + TWO*C*B
375 * If eigenvectors are desired, then save rotations.
377 IF( ICOMPZ.GT.0 ) THEN
384 * If eigenvectors are desired, then apply saved rotations.
386 IF( ICOMPZ.GT.0 ) THEN
388 CALL ZLASR( 'R', 'V', 'B', N, MM, WORK( L ), WORK( N-1+L ),
410 * Look for small superdiagonal element.
415 DO 100 M = L, LENDP1, -1
416 TST = ABS( E( M-1 ) )**2
417 IF( TST.LE.( EPS2*ABS( D( M ) ) )*ABS( D( M-1 ) )+
431 * If remaining matrix is 2-by-2, use DLAE2 or SLAEV2
432 * to compute its eigensystem.
435 IF( ICOMPZ.GT.0 ) THEN
436 CALL DLAEV2( D( L-1 ), E( L-1 ), D( L ), RT1, RT2, C, S )
439 CALL ZLASR( 'R', 'V', 'F', N, 2, WORK( M ),
440 $ WORK( N-1+M ), Z( 1, L-1 ), LDZ )
442 CALL DLAE2( D( L-1 ), E( L-1 ), D( L ), RT1, RT2 )
459 G = ( D( L-1 )-P ) / ( TWO*E( L-1 ) )
461 G = D( M ) - P + ( E( L-1 ) / ( G+SIGN( R, G ) ) )
473 CALL DLARTG( G, F, C, S, R )
477 R = ( D( I+1 )-G )*S + TWO*C*B
482 * If eigenvectors are desired, then save rotations.
484 IF( ICOMPZ.GT.0 ) THEN
491 * If eigenvectors are desired, then apply saved rotations.
493 IF( ICOMPZ.GT.0 ) THEN
495 CALL ZLASR( 'R', 'V', 'F', N, MM, WORK( M ), WORK( N-1+M ),
515 * Undo scaling if necessary
518 IF( ISCALE.EQ.1 ) THEN
519 CALL DLASCL( 'G', 0, 0, SSFMAX, ANORM, LENDSV-LSV+1, 1,
520 $ D( LSV ), N, INFO )
521 CALL DLASCL( 'G', 0, 0, SSFMAX, ANORM, LENDSV-LSV, 1, E( LSV ),
523 ELSE IF( ISCALE.EQ.2 ) THEN
524 CALL DLASCL( 'G', 0, 0, SSFMIN, ANORM, LENDSV-LSV+1, 1,
525 $ D( LSV ), N, INFO )
526 CALL DLASCL( 'G', 0, 0, SSFMIN, ANORM, LENDSV-LSV, 1, E( LSV ),
530 * Check for no convergence to an eigenvalue after a total
531 * of N*MAXIT iterations.
533 IF( JTOT.EQ.NMAXIT ) THEN
542 * Order eigenvalues and eigenvectors.
545 IF( ICOMPZ.EQ.0 ) THEN
549 CALL DLASRT( 'I', N, D, INFO )
553 * Use Selection Sort to minimize swaps of eigenvectors
560 IF( D( J ).LT.P ) THEN
568 CALL ZSWAP( N, Z( 1, I ), 1, Z( 1, K ), 1 )