1 SUBROUTINE ZHPGVX
( ITYPE
, JOBZ
, RANGE
, UPLO
, N
, AP
, BP
, VL
, VU
,
2 $ IL
, IU
, ABSTOL
, M
, W
, Z
, LDZ
, WORK
, 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
, ITYPE
, IU
, LDZ
, M
, N
12 DOUBLE PRECISION ABSTOL
, VL
, VU
14 * .. Array Arguments
..
15 INTEGER IFAIL
( * ), IWORK
( * )
16 DOUBLE PRECISION RWORK
( * ), W
( * )
17 COMPLEX*16 AP
( * ), BP
( * ), WORK
( * ), Z
( LDZ
, * )
23 * ZHPGVX computes selected eigenvalues and
, optionally
, eigenvectors
24 * of a
complex generalized Hermitian
-definite eigenproblem
, of the form
25 * A*x
=(lambda
)*B*x
, A*Bx
=(lambda
)*x
, or B*A*x
=(lambda
)*x
. Here A and
26 * B are assumed
to be Hermitian
, stored in packed
format, and B is also
27 * positive definite
. Eigenvalues and eigenvectors can be selected by
28 * specifying either a range of values or a range of indices
for the
29 * desired eigenvalues
.
34 * ITYPE
(input
) INTEGER
35 * Specifies the problem type
to be solved
:
36 * = 1: A*x
= (lambda
)*B*x
37 * = 2: A*B*x
= (lambda
)*x
38 * = 3: B*A*x
= (lambda
)*x
40 * JOBZ
(input
) CHARACTER*1
41 * = 'N': Compute eigenvalues only
;
42 * = 'V': Compute eigenvalues and eigenvectors
.
44 * RANGE
(input
) CHARACTER*1
45 * = 'A': all eigenvalues will be found
;
46 * = 'V': all eigenvalues in the half
-open interval
(VL
,VU
]
48 * = 'I': the IL
-th through IU
-th eigenvalues will be found
.
50 * UPLO
(input
) CHARACTER*1
51 * = 'U': Upper triangles of A and B are stored
;
52 * = 'L': Lower triangles of A and B are stored
.
55 * The order of the matrices A and B
. N
>= 0.
57 * AP
(input
/output
) COMPLEX*16 array
, dimension (N*
(N
+1)/2)
58 * On entry
, the upper or lower triangle of the Hermitian matrix
59 * A
, packed columnwise in a linear array
. The j
-th column of A
60 * is stored in the array AP as follows
:
61 * if UPLO
= 'U', AP
(i
+ (j
-1)*j
/2) = A
(i
,j
) for 1<=i
<=j
;
62 * if UPLO
= 'L', AP
(i
+ (j
-1)*(2*n
-j
)/2) = A
(i
,j
) for j
<=i
<=n
.
64 * On exit
, the contents of AP are destroyed
.
66 * BP
(input
/output
) COMPLEX*16 array
, dimension (N*
(N
+1)/2)
67 * On entry
, the upper or lower triangle of the Hermitian matrix
68 * B
, packed columnwise in a linear array
. The j
-th column of B
69 * is stored in the array BP as follows
:
70 * if UPLO
= 'U', BP
(i
+ (j
-1)*j
/2) = B
(i
,j
) for 1<=i
<=j
;
71 * if UPLO
= 'L', BP
(i
+ (j
-1)*(2*n
-j
)/2) = B
(i
,j
) for j
<=i
<=n
.
73 * On exit
, the triangular factor U or L from the Cholesky
74 * factorization B
= U**H*U or B
= L*L**H
, in the same storage
77 * VL
(input
) DOUBLE PRECISION
78 * VU
(input
) DOUBLE PRECISION
79 * If RANGE
='V', the lower and upper bounds of the interval
to
80 * be searched
for eigenvalues
. VL
< VU
.
81 * Not referenced
if RANGE
= 'A' or
'I'.
85 * If RANGE
='I', the indices
(in ascending order
) of the
86 * smallest and largest eigenvalues
to be returned
.
87 * 1 <= IL
<= IU
<= N
, if N
> 0; IL
= 1 and IU
= 0 if N
= 0.
88 * Not referenced
if RANGE
= 'A' or
'V'.
90 * ABSTOL
(input
) DOUBLE PRECISION
91 * The absolute error tolerance
for the eigenvalues
.
92 * An approximate eigenvalue is accepted as converged
93 * when it is determined
to lie in an interval
[a
,b
]
94 * of width less than or equal
to
96 * ABSTOL
+ EPS
* max
( |a|
,|b|
) ,
98 * where EPS is the machine
precision. If ABSTOL is less than
99 * or equal
to zero
, then EPS*|T| will be used in its place
,
100 * where |T| is the
1-norm of the tridiagonal matrix obtained
101 * by reducing AP
to tridiagonal form
.
103 * Eigenvalues will be computed most accurately when ABSTOL is
104 * set
to twice the underflow threshold
2*DLAMCH
('S'), not zero
.
105 * If this routine returns with INFO
>0, indicating that some
106 * eigenvectors did not converge
, try setting ABSTOL
to
110 * The total number of eigenvalues found
. 0 <= M
<= N
.
111 * If RANGE
= 'A', M
= N
, and
if RANGE
= 'I', M
= IU
-IL
+1.
113 * W
(output
) DOUBLE PRECISION array
, dimension (N
)
114 * On normal exit
, the first M elements contain the selected
115 * eigenvalues in ascending order
.
117 * Z
(output
) COMPLEX*16 array
, dimension (LDZ
, N
)
118 * If JOBZ
= 'N', then Z is not referenced
.
119 * If JOBZ
= 'V', then if INFO
= 0, the first M columns of Z
120 * contain the orthonormal eigenvectors of the matrix A
121 * corresponding
to the selected eigenvalues
, with the i
-th
122 * column of Z holding the eigenvector associated with W
(i
).
123 * The eigenvectors are normalized as follows
:
124 * if ITYPE
= 1 or
2, Z**H*B*Z
= I
;
125 * if ITYPE
= 3, Z**H*inv
(B
)*Z
= I
.
127 * If an eigenvector fails
to converge
, then that column of Z
128 * contains the latest approximation
to the eigenvector
, and the
129 * index of the eigenvector is returned in IFAIL
.
130 * Note
: the user must ensure that at least max
(1,M
) columns are
131 * supplied in the array Z
; if RANGE
= 'V', the exact value of M
132 * is not known in advance and an upper bound must be used
.
134 * LDZ
(input
) INTEGER
135 * The leading
dimension of the array Z
. LDZ
>= 1, and
if
136 * JOBZ
= 'V', LDZ
>= max
(1,N
).
138 * WORK
(workspace
) COMPLEX*16 array
, dimension (2*N
)
140 * RWORK
(workspace
) DOUBLE PRECISION array
, dimension (7*N
)
142 * IWORK
(workspace
) INTEGER array
, dimension (5*N
)
144 * IFAIL
(output
) INTEGER array
, dimension (N
)
145 * If JOBZ
= 'V', then if INFO
= 0, the first M elements of
146 * IFAIL are zero
. If INFO
> 0, then IFAIL contains the
147 * indices of the eigenvectors that failed
to converge
.
148 * If JOBZ
= 'N', then IFAIL is not referenced
.
150 * INFO
(output
) INTEGER
151 * = 0: successful exit
152 * < 0: if INFO
= -i
, the i
-th argument had an illegal value
153 * > 0: ZPPTRF or ZHPEVX returned an error code
:
154 * <= N
: if INFO
= i
, ZHPEVX failed
to converge
;
155 * i eigenvectors failed
to converge
. Their indices
156 * are stored in array IFAIL
.
157 * > N
: if INFO
= N
+ i
, for 1 <= i
<= n
, then the leading
158 * minor of order i of B is not positive definite
.
159 * The factorization of B could not be completed and
160 * no eigenvalues or eigenvectors were computed
.
165 * Based on contributions by
166 * Mark Fahey
, Department of Mathematics
, Univ
. of Kentucky
, USA
168 * =====================================================================
170 * .. Local Scalars
..
171 LOGICAL ALLEIG
, INDEIG
, UPPER
, VALEIG
, WANTZ
175 * .. External Functions
..
179 * .. External Subroutines
..
180 EXTERNAL XERBLA
, ZHPEVX
, ZHPGST
, ZPPTRF
, ZTPMV
, ZTPSV
182 * .. Intrinsic Functions
..
185 * .. Executable Statements
..
187 * Test the input parameters
.
189 WANTZ
= LSAME
( JOBZ
, 'V' )
190 UPPER
= LSAME
( UPLO
, 'U' )
191 ALLEIG
= LSAME
( RANGE
, 'A' )
192 VALEIG
= LSAME
( RANGE
, 'V' )
193 INDEIG
= LSAME
( RANGE
, 'I' )
196 IF( ITYPE
.LT
.1 .OR
. ITYPE
.GT
.3 ) THEN
198 ELSE IF( .NOT
.( WANTZ
.OR
. LSAME
( JOBZ
, 'N' ) ) ) THEN
200 ELSE IF( .NOT
.( ALLEIG
.OR
. VALEIG
.OR
. INDEIG
) ) THEN
202 ELSE IF( .NOT
.( UPPER
.OR
. LSAME
( UPLO
, 'L' ) ) ) THEN
204 ELSE IF( N
.LT
.0 ) THEN
208 IF( N
.GT
.0 .AND
. VU
.LE
.VL
) THEN
211 ELSE IF( INDEIG
) THEN
214 ELSE IF( IU
.LT
.MIN
( N
, IL
) .OR
. IU
.GT
.N
) THEN
220 IF( LDZ
.LT
.1 .OR
. ( WANTZ
.AND
. LDZ
.LT
.N
) ) THEN
226 CALL XERBLA
( 'ZHPGVX', -INFO
)
230 * Quick
return if possible
235 * Form a Cholesky factorization of B
.
237 CALL ZPPTRF
( UPLO
, N
, BP
, INFO
)
243 * Transform problem
to standard eigenvalue problem and solve
.
245 CALL ZHPGST
( ITYPE
, UPLO
, N
, AP
, BP
, INFO
)
246 CALL ZHPEVX
( JOBZ
, RANGE
, UPLO
, N
, AP
, VL
, VU
, IL
, IU
, ABSTOL
, M
,
247 $ W
, Z
, LDZ
, WORK
, RWORK
, IWORK
, IFAIL
, INFO
)
251 * Backtransform eigenvectors
to the original problem
.
255 IF( ITYPE
.EQ
.1 .OR
. ITYPE
.EQ
.2 ) THEN
257 * For A*x
=(lambda
)*B*x and A*B*x
=(lambda
)*x
;
258 * backtransform eigenvectors
: x
= inv
(L
)'*y or inv(U)*y
267 CALL ZTPSV( UPLO, TRANS, 'Non
-unit
', N, BP, Z( 1, J ),
271 ELSE IF( ITYPE.EQ.3 ) THEN
273 * For B*A*x=(lambda)*x;
274 * backtransform eigenvectors: x = L*y or U'*y
283 CALL ZTPMV
( UPLO
, TRANS
, 'Non-unit', N
, BP
, Z
( 1, J
),