1CHPGVX(1) LAPACK driver routine (version 3.2) CHPGVX(1)
2
3
4
6 CHPGVX - computes selected eigenvalues and, optionally, eigenvectors of
7 a complex generalized Hermitian-definite eigenproblem, of the form
8 A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x
9
11 SUBROUTINE CHPGVX( ITYPE, JOBZ, RANGE, UPLO, N, AP, BP, VL, VU, IL, IU,
12 ABSTOL, M, W, Z, LDZ, WORK, RWORK, IWORK, IFAIL,
13 INFO )
14
15 CHARACTER JOBZ, RANGE, UPLO
16
17 INTEGER IL, INFO, ITYPE, IU, LDZ, M, N
18
19 REAL ABSTOL, VL, VU
20
21 INTEGER IFAIL( * ), IWORK( * )
22
23 REAL RWORK( * ), W( * )
24
25 COMPLEX AP( * ), BP( * ), WORK( * ), Z( LDZ, * )
26
28 CHPGVX computes selected eigenvalues and, optionally, eigenvectors of a
29 complex generalized Hermitian-definite eigenproblem, of the form
30 A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x. Here A and B
31 are assumed to be Hermitian, stored in packed format, and B is also
32 positive definite. Eigenvalues and eigenvectors can be selected by
33 specifying either a range of values or a range of indices for the
34 desired eigenvalues.
35
37 ITYPE (input) INTEGER
38 Specifies the problem type to be solved:
39 = 1: A*x = (lambda)*B*x
40 = 2: A*B*x = (lambda)*x
41 = 3: B*A*x = (lambda)*x
42
43 JOBZ (input) CHARACTER*1
44 = 'N': Compute eigenvalues only;
45 = 'V': Compute eigenvalues and eigenvectors.
46
47 RANGE (input) CHARACTER*1
48 = 'A': all eigenvalues will be found;
49 = 'V': all eigenvalues in the half-open interval (VL,VU] will
50 be found; = 'I': the IL-th through IU-th eigenvalues will be
51 found.
52
53 UPLO (input) CHARACTER*1
54 = 'U': Upper triangles of A and B are stored;
55 = 'L': Lower triangles of A and B are stored.
56
57 N (input) INTEGER
58 The order of the matrices A and B. N >= 0.
59
60 AP (input/output) COMPLEX array, dimension (N*(N+1)/2)
61 On entry, the upper or lower triangle of the Hermitian matrix
62 A, packed columnwise in a linear array. The j-th column of A
63 is stored in the array AP as follows: if UPLO = 'U', AP(i +
64 (j-1)*j/2) = A(i,j) for 1<=i<=j; if UPLO = 'L', AP(i +
65 (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n. On exit, the contents
66 of AP are destroyed.
67
68 BP (input/output) COMPLEX array, dimension (N*(N+1)/2)
69 On entry, the upper or lower triangle of the Hermitian matrix
70 B, packed columnwise in a linear array. The j-th column of B
71 is stored in the array BP as follows: if UPLO = 'U', BP(i +
72 (j-1)*j/2) = B(i,j) for 1<=i<=j; if UPLO = 'L', BP(i +
73 (j-1)*(2*n-j)/2) = B(i,j) for j<=i<=n. On exit, the triangular
74 factor U or L from the Cholesky factorization B = U**H*U or B =
75 L*L**H, in the same storage format as B.
76
77 VL (input) REAL
78 VU (input) REAL If RANGE='V', the lower and upper bounds
79 of the interval to be searched for eigenvalues. VL < VU. Not
80 referenced if RANGE = 'A' or 'I'.
81
82 IL (input) INTEGER
83 IU (input) INTEGER If RANGE='I', the indices (in ascending
84 order) of the smallest and largest eigenvalues to be returned.
85 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0. Not
86 referenced if RANGE = 'A' or 'V'.
87
88 ABSTOL (input) REAL
89 The absolute error tolerance for the eigenvalues. An approxi‐
90 mate eigenvalue is accepted as converged when it is determined
91 to lie in an interval [a,b] of width less than or equal to
92 ABSTOL + EPS * max( |a|,|b| ) , where EPS is the machine pre‐
93 cision. If ABSTOL is less than or equal to zero, then EPS*|T|
94 will be used in its place, where |T| is the 1-norm of the
95 tridiagonal matrix obtained by reducing AP to tridiagonal form.
96 Eigenvalues will be computed most accurately when ABSTOL is set
97 to twice the underflow threshold 2*SLAMCH('S'), not zero. If
98 this routine returns with INFO>0, indicating that some eigen‐
99 vectors did not converge, try setting ABSTOL to 2*SLAMCH('S').
100
101 M (output) INTEGER
102 The total number of eigenvalues found. 0 <= M <= N. If RANGE
103 = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
104
105 W (output) REAL array, dimension (N)
106 On normal exit, the first M elements contain the selected ei‐
107 genvalues in ascending order.
108
109 Z (output) COMPLEX array, dimension (LDZ, N)
110 If JOBZ = 'N', then Z is not referenced. If JOBZ = 'V', then
111 if INFO = 0, the first M columns of Z contain the orthonormal
112 eigenvectors of the matrix A corresponding to the selected ei‐
113 genvalues, with the i-th column of Z holding the eigenvector
114 associated with W(i). The eigenvectors are normalized as fol‐
115 lows: if ITYPE = 1 or 2, Z**H*B*Z = I; if ITYPE = 3,
116 Z**H*inv(B)*Z = I. If an eigenvector fails to converge, then
117 that column of Z contains the latest approximation to the
118 eigenvector, and the index of the eigenvector is returned in
119 IFAIL. Note: the user must ensure that at least max(1,M) col‐
120 umns are supplied in the array Z; if RANGE = 'V', the exact
121 value of M is not known in advance and an upper bound must be
122 used.
123
124 LDZ (input) INTEGER
125 The leading dimension of the array Z. LDZ >= 1, and if JOBZ =
126 'V', LDZ >= max(1,N).
127
128 WORK (workspace) COMPLEX array, dimension (2*N)
129
130 RWORK (workspace) REAL array, dimension (7*N)
131
132 IWORK (workspace) INTEGER array, dimension (5*N)
133
134 IFAIL (output) INTEGER array, dimension (N)
135 If JOBZ = 'V', then if INFO = 0, the first M elements of IFAIL
136 are zero. If INFO > 0, then IFAIL contains the indices of the
137 eigenvectors that failed to converge. If JOBZ = 'N', then
138 IFAIL is not referenced.
139
140 INFO (output) INTEGER
141 = 0: successful exit
142 < 0: if INFO = -i, the i-th argument had an illegal value
143 > 0: CPPTRF or CHPEVX returned an error code:
144 <= N: if INFO = i, CHPEVX failed to converge; i eigenvectors
145 failed to converge. Their indices are stored in array IFAIL.
146 > N: if INFO = N + i, for 1 <= i <= n, then the leading minor
147 of order i of B is not positive definite. The factorization of
148 B could not be completed and no eigenvalues or eigenvectors
149 were computed.
150
152 Based on contributions by
153 Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
154
155
156
157 LAPACK driver routine (version 3.N2o)vember 2008 CHPGVX(1)