1 SUBROUTINE ZHEEVX
( JOBZ
, RANGE
, UPLO
, N
, A
, LDA
, VL
, VU
, IL
, IU
,
2 $ ABSTOL
, M
, W
, Z
, LDZ
, WORK
, LWORK
, RWORK
,
5 * -- LAPACK driver routine
(version
3.1) --
6 * Univ
. of Tennessee
, Univ
. of California Berkeley and NAG Ltd
..
9 * .. Scalar Arguments
..
10 CHARACTER JOBZ
, RANGE
, UPLO
11 INTEGER IL
, INFO
, IU
, LDA
, LDZ
, LWORK
, M
, N
12 DOUBLE PRECISION ABSTOL
, VL
, VU
14 * .. Array Arguments
..
15 INTEGER IFAIL
( * ), IWORK
( * )
16 DOUBLE PRECISION RWORK
( * ), W
( * )
17 COMPLEX*16 A
( LDA
, * ), WORK
( * ), Z
( LDZ
, * )
23 * ZHEEVX computes selected eigenvalues and
, optionally
, eigenvectors
24 * of a
complex Hermitian matrix A
. Eigenvalues and eigenvectors can
25 * be selected by specifying either a range of values or a range of
26 * indices
for the desired eigenvalues
.
31 * JOBZ
(input
) CHARACTER*1
32 * = 'N': Compute eigenvalues only
;
33 * = 'V': Compute eigenvalues and eigenvectors
.
35 * RANGE
(input
) CHARACTER*1
36 * = 'A': all eigenvalues will be found
.
37 * = 'V': all eigenvalues in the half
-open interval
(VL
,VU
]
39 * = 'I': the IL
-th through IU
-th eigenvalues will be found
.
41 * UPLO
(input
) CHARACTER*1
42 * = 'U': Upper triangle of A is stored
;
43 * = 'L': Lower triangle of A is stored
.
46 * The order of the matrix A
. N
>= 0.
48 * A
(input
/output
) COMPLEX*16 array
, dimension (LDA
, N
)
49 * On entry
, the Hermitian matrix A
. If UPLO
= 'U', the
50 * leading N
-by
-N upper triangular part of A contains the
51 * upper triangular part of the matrix A
. If UPLO
= 'L',
52 * the leading N
-by
-N lower triangular part of A contains
53 * the lower triangular part of the matrix A
.
54 * On exit
, the lower triangle
(if UPLO
='L') or the upper
55 * triangle
(if UPLO
='U') of A
, including the diagonal
, is
59 * The leading
dimension of the array A
. LDA
>= max
(1,N
).
61 * VL
(input
) DOUBLE PRECISION
62 * VU
(input
) DOUBLE PRECISION
63 * If RANGE
='V', the lower and upper bounds of the interval
to
64 * be searched
for eigenvalues
. VL
< VU
.
65 * Not referenced
if RANGE
= 'A' or
'I'.
69 * If RANGE
='I', the indices
(in ascending order
) of the
70 * smallest and largest eigenvalues
to be returned
.
71 * 1 <= IL
<= IU
<= N
, if N
> 0; IL
= 1 and IU
= 0 if N
= 0.
72 * Not referenced
if RANGE
= 'A' or
'V'.
74 * ABSTOL
(input
) DOUBLE PRECISION
75 * The absolute error tolerance
for the eigenvalues
.
76 * An approximate eigenvalue is accepted as converged
77 * when it is determined
to lie in an interval
[a
,b
]
78 * of width less than or equal
to
80 * ABSTOL
+ EPS
* max
( |a|
,|b|
) ,
82 * where EPS is the machine
precision. If ABSTOL is less than
83 * or equal
to zero
, then EPS*|T| will be used in its place
,
84 * where |T| is the
1-norm of the tridiagonal matrix obtained
85 * by reducing A
to tridiagonal form
.
87 * Eigenvalues will be computed most accurately when ABSTOL is
88 * set
to twice the underflow threshold
2*DLAMCH
('S'), not zero
.
89 * If this routine returns with INFO
>0, indicating that some
90 * eigenvectors did not converge
, try setting ABSTOL
to
93 * See
"Computing Small Singular Values of Bidiagonal Matrices
94 * with Guaranteed High Relative Accuracy," by Demmel and
95 * Kahan
, LAPACK Working Note #
3.
98 * The total number of eigenvalues found
. 0 <= M
<= N
.
99 * If RANGE
= 'A', M
= N
, and
if RANGE
= 'I', M
= IU
-IL
+1.
101 * W
(output
) DOUBLE PRECISION array
, dimension (N
)
102 * On normal exit
, the first M elements contain the selected
103 * eigenvalues in ascending order
.
105 * Z
(output
) COMPLEX*16 array
, dimension (LDZ
, max
(1,M
))
106 * If JOBZ
= 'V', then if INFO
= 0, the first M columns of Z
107 * contain the orthonormal eigenvectors of the matrix A
108 * corresponding
to the selected eigenvalues
, with the i
-th
109 * column of Z holding the eigenvector associated with W
(i
).
110 * If an eigenvector fails
to converge
, then that column of Z
111 * contains the latest approximation
to the eigenvector
, and the
112 * index of the eigenvector is returned in IFAIL
.
113 * If JOBZ
= 'N', then Z is not referenced
.
114 * Note
: the user must ensure that at least max
(1,M
) columns are
115 * supplied in the array Z
; if RANGE
= 'V', the exact value of M
116 * is not known in advance and an upper bound must be used
.
118 * LDZ
(input
) INTEGER
119 * The leading
dimension of the array Z
. LDZ
>= 1, and
if
120 * JOBZ
= 'V', LDZ
>= max
(1,N
).
122 * WORK
(workspace
/output
) COMPLEX*16 array
, dimension (MAX
(1,LWORK
))
123 * On exit
, if INFO
= 0, WORK
(1) returns the optimal LWORK
.
125 * LWORK
(input
) INTEGER
126 * The length of the array WORK
. LWORK
>= 1, when N
<= 1;
128 * For optimal efficiency
, LWORK
>= (NB
+1)*N
,
129 * where NB is the max of the blocksize
for ZHETRD and
for
130 * ZUNMTR as returned by ILAENV
.
132 * If LWORK
= -1, then a workspace query is assumed
; the routine
133 * only calculates the optimal size of the WORK array
, returns
134 * this value as the first entry of the WORK array
, and no error
135 * message related
to LWORK is issued by XERBLA
.
137 * RWORK
(workspace
) DOUBLE PRECISION array
, dimension (7*N
)
139 * IWORK
(workspace
) INTEGER array
, dimension (5*N
)
141 * IFAIL
(output
) INTEGER array
, dimension (N
)
142 * If JOBZ
= 'V', then if INFO
= 0, the first M elements of
143 * IFAIL are zero
. If INFO
> 0, then IFAIL contains the
144 * indices of the eigenvectors that failed
to converge
.
145 * If JOBZ
= 'N', then IFAIL is not referenced
.
147 * INFO
(output
) INTEGER
148 * = 0: successful exit
149 * < 0: if INFO
= -i
, the i
-th argument had an illegal value
150 * > 0: if INFO
= i
, then i eigenvectors failed
to converge
.
151 * Their indices are stored in array IFAIL
.
153 * =====================================================================
156 DOUBLE PRECISION ZERO
, ONE
157 PARAMETER ( ZERO
= 0.0D
+0, ONE
= 1.0D
+0 )
159 PARAMETER ( CONE
= ( 1.0D
+0, 0.0D
+0 ) )
161 * .. Local Scalars
..
162 LOGICAL ALLEIG
, INDEIG
, LOWER
, LQUERY
, TEST
, VALEIG
,
165 INTEGER I
, IINFO
, IMAX
, INDD
, INDE
, INDEE
, INDIBL
,
166 $ INDISP
, INDIWK
, INDRWK
, INDTAU
, INDWRK
, ISCALE
,
167 $ ITMP1
, J
, JJ
, LLWORK
, LWKMIN
, LWKOPT
, NB
,
169 DOUBLE PRECISION ABSTLL
, ANRM
, BIGNUM
, EPS
, RMAX
, RMIN
, SAFMIN
,
170 $ SIGMA
, SMLNUM
, TMP1
, VLL
, VUU
172 * .. External Functions
..
175 DOUBLE PRECISION DLAMCH
, ZLANHE
176 EXTERNAL LSAME
, ILAENV
, DLAMCH
, ZLANHE
178 * .. External Subroutines
..
179 EXTERNAL DCOPY
, DSCAL
, DSTEBZ
, DSTERF
, XERBLA
, ZDSCAL
,
180 $ ZHETRD
, ZLACPY
, ZSTEIN
, ZSTEQR
, ZSWAP
, ZUNGTR
,
183 * .. Intrinsic Functions
..
184 INTRINSIC DBLE
, MAX
, MIN
, SQRT
186 * .. Executable Statements
..
188 * Test the input parameters
.
190 LOWER
= LSAME
( UPLO
, 'L' )
191 WANTZ
= LSAME
( JOBZ
, 'V' )
192 ALLEIG
= LSAME
( RANGE
, 'A' )
193 VALEIG
= LSAME
( RANGE
, 'V' )
194 INDEIG
= LSAME
( RANGE
, 'I' )
195 LQUERY
= ( LWORK
.EQ
.-1 )
198 IF( .NOT
.( WANTZ
.OR
. LSAME
( JOBZ
, 'N' ) ) ) THEN
200 ELSE IF( .NOT
.( ALLEIG
.OR
. VALEIG
.OR
. INDEIG
) ) THEN
202 ELSE IF( .NOT
.( LOWER
.OR
. LSAME
( UPLO
, 'U' ) ) ) THEN
204 ELSE IF( N
.LT
.0 ) THEN
206 ELSE IF( LDA
.LT
.MAX
( 1, N
) ) THEN
210 IF( N
.GT
.0 .AND
. VU
.LE
.VL
)
212 ELSE IF( INDEIG
) THEN
213 IF( IL
.LT
.1 .OR
. IL
.GT
.MAX
( 1, N
) ) THEN
215 ELSE IF( IU
.LT
.MIN
( N
, IL
) .OR
. IU
.GT
.N
) THEN
221 IF( LDZ
.LT
.1 .OR
. ( WANTZ
.AND
. LDZ
.LT
.N
) ) THEN
232 NB
= ILAENV
( 1, 'ZHETRD', UPLO
, N
, -1, -1, -1 )
233 NB
= MAX
( NB
, ILAENV
( 1, 'ZUNMTR', UPLO
, N
, -1, -1, -1 ) )
234 LWKOPT
= MAX
( 1, ( NB
+ 1 )*N
)
238 IF( LWORK
.LT
.MAX
( 1, 2*N
) .AND
. .NOT
.LQUERY
)
243 CALL XERBLA
( 'ZHEEVX', -INFO
)
245 ELSE IF( LQUERY
) THEN
249 * Quick
return if possible
257 IF( ALLEIG
.OR
. INDEIG
) THEN
260 ELSE IF( VALEIG
) THEN
261 IF( VL
.LT
.DBLE
( A
( 1, 1 ) ) .AND
. VU
.GE
.DBLE
( A
( 1, 1 ) ) )
272 * Get machine constants
.
274 SAFMIN
= DLAMCH
( 'Safe minimum' )
275 EPS
= DLAMCH
( 'Precision' )
276 SMLNUM
= SAFMIN
/ EPS
277 BIGNUM
= ONE
/ SMLNUM
278 RMIN
= SQRT
( SMLNUM
)
279 RMAX
= MIN
( SQRT
( BIGNUM
), ONE
/ SQRT
( SQRT
( SAFMIN
) ) )
281 * Scale matrix
to allowable range
, if necessary
.
289 ANRM
= ZLANHE
( 'M', UPLO
, N
, A
, LDA
, RWORK
)
290 IF( ANRM
.GT
.ZERO
.AND
. ANRM
.LT
.RMIN
) THEN
293 ELSE IF( ANRM
.GT
.RMAX
) THEN
297 IF( ISCALE
.EQ
.1 ) THEN
300 CALL ZDSCAL
( N
-J
+1, SIGMA
, A
( J
, J
), 1 )
304 CALL ZDSCAL
( J
, SIGMA
, A
( 1, J
), 1 )
308 $ ABSTLL
= ABSTOL*SIGMA
315 * Call ZHETRD
to reduce Hermitian matrix
to tridiagonal form
.
322 LLWORK
= LWORK
- INDWRK
+ 1
323 CALL ZHETRD
( UPLO
, N
, A
, LDA
, RWORK
( INDD
), RWORK
( INDE
),
324 $ WORK
( INDTAU
), WORK
( INDWRK
), LLWORK
, IINFO
)
326 * If all eigenvalues are desired and ABSTOL is less than or equal
to
327 * zero
, then call DSTERF or ZUNGTR and ZSTEQR
. If this fails
for
328 * some eigenvalue
, then try DSTEBZ
.
332 IF( IL
.EQ
.1 .AND
. IU
.EQ
.N
) THEN
336 IF( ( ALLEIG
.OR
. TEST
) .AND
. ( ABSTOL
.LE
.ZERO
) ) THEN
337 CALL DCOPY
( N
, RWORK
( INDD
), 1, W
, 1 )
339 IF( .NOT
.WANTZ
) THEN
340 CALL DCOPY
( N
-1, RWORK
( INDE
), 1, RWORK
( INDEE
), 1 )
341 CALL DSTERF
( N
, W
, RWORK
( INDEE
), INFO
)
343 CALL ZLACPY
( 'A', N
, N
, A
, LDA
, Z
, LDZ
)
344 CALL ZUNGTR
( UPLO
, N
, Z
, LDZ
, WORK
( INDTAU
),
345 $ WORK
( INDWRK
), LLWORK
, IINFO
)
346 CALL DCOPY
( N
-1, RWORK
( INDE
), 1, RWORK
( INDEE
), 1 )
347 CALL ZSTEQR
( JOBZ
, N
, W
, RWORK
( INDEE
), Z
, LDZ
,
348 $ RWORK
( INDRWK
), INFO
)
362 * Otherwise
, call DSTEBZ and
, if eigenvectors are desired
, ZSTEIN
.
372 CALL DSTEBZ
( RANGE
, ORDER
, N
, VLL
, VUU
, IL
, IU
, ABSTLL
,
373 $ RWORK
( INDD
), RWORK
( INDE
), M
, NSPLIT
, W
,
374 $ IWORK
( INDIBL
), IWORK
( INDISP
), RWORK
( INDRWK
),
375 $ IWORK
( INDIWK
), INFO
)
378 CALL ZSTEIN
( N
, RWORK
( INDD
), RWORK
( INDE
), M
, W
,
379 $ IWORK
( INDIBL
), IWORK
( INDISP
), Z
, LDZ
,
380 $ RWORK
( INDRWK
), IWORK
( INDIWK
), IFAIL
, INFO
)
382 * Apply unitary matrix used in reduction
to tridiagonal
383 * form
to eigenvectors returned by ZSTEIN
.
385 CALL ZUNMTR
( 'L', UPLO
, 'N', N
, M
, A
, LDA
, WORK
( INDTAU
), Z
,
386 $ LDZ
, WORK
( INDWRK
), LLWORK
, IINFO
)
389 * If matrix was scaled
, then rescale eigenvalues appropriately
.
392 IF( ISCALE
.EQ
.1 ) THEN
398 CALL DSCAL
( IMAX
, ONE
/ SIGMA
, W
, 1 )
401 * If eigenvalues are not in order
, then sort them
, along with
409 IF( W
( JJ
).LT
.TMP1
) THEN
416 ITMP1
= IWORK
( INDIBL
+I
-1 )
418 IWORK
( INDIBL
+I
-1 ) = IWORK
( INDIBL
+J
-1 )
420 IWORK
( INDIBL
+J
-1 ) = ITMP1
421 CALL ZSWAP
( N
, Z
( 1, I
), 1, Z
( 1, J
), 1 )
424 IFAIL
( I
) = IFAIL
( J
)
431 * Set WORK
(1) to optimal
complex workspace size
.