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