1ZHBEVX(1) LAPACK driver routine (version 3.2) ZHBEVX(1)
2
3
4
6 ZHBEVX - computes selected eigenvalues and, optionally, eigenvectors of
7 a complex Hermitian band matrix A
8
10 SUBROUTINE ZHBEVX( JOBZ, RANGE, UPLO, N, KD, AB, LDAB, Q, LDQ, VL, VU,
11 IL, IU, ABSTOL, M, W, Z, LDZ, WORK, RWORK, IWORK,
12 IFAIL, INFO )
13
14 CHARACTER JOBZ, RANGE, UPLO
15
16 INTEGER IL, INFO, IU, KD, LDAB, LDQ, LDZ, M, N
17
18 DOUBLE PRECISION ABSTOL, VL, VU
19
20 INTEGER IFAIL( * ), IWORK( * )
21
22 DOUBLE PRECISION RWORK( * ), W( * )
23
24 COMPLEX*16 AB( LDAB, * ), Q( LDQ, * ), WORK( * ), Z( LDZ, * )
25
27 ZHBEVX computes selected eigenvalues and, optionally, eigenvectors of a
28 complex Hermitian band matrix A. Eigenvalues and eigenvectors can be
29 selected by specifying either a range of values or a range of indices
30 for the desired eigenvalues.
31
33 JOBZ (input) CHARACTER*1
34 = 'N': Compute eigenvalues only;
35 = 'V': Compute eigenvalues and eigenvectors.
36
37 RANGE (input) CHARACTER*1
38 = 'A': all eigenvalues will be found;
39 = 'V': all eigenvalues in the half-open interval (VL,VU] will
40 be found; = 'I': the IL-th through IU-th eigenvalues will be
41 found.
42
43 UPLO (input) CHARACTER*1
44 = 'U': Upper triangle of A is stored;
45 = 'L': Lower triangle of A is stored.
46
47 N (input) INTEGER
48 The order of the matrix A. N >= 0.
49
50 KD (input) INTEGER
51 The number of superdiagonals of the matrix A if UPLO = 'U', or
52 the number of subdiagonals if UPLO = 'L'. KD >= 0.
53
54 AB (input/output) COMPLEX*16 array, dimension (LDAB, N)
55 On entry, the upper or lower triangle of the Hermitian band
56 matrix A, stored in the first KD+1 rows of the array. The j-th
57 column of A is stored in the j-th column of the array AB as
58 follows: if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-
59 kd)<=i<=j; if UPLO = 'L', AB(1+i-j,j) = A(i,j) for
60 j<=i<=min(n,j+kd). On exit, AB is overwritten by values gener‐
61 ated during the reduction to tridiagonal form.
62
63 LDAB (input) INTEGER
64 The leading dimension of the array AB. LDAB >= KD + 1.
65
66 Q (output) COMPLEX*16 array, dimension (LDQ, N)
67 If JOBZ = 'V', the N-by-N unitary matrix used in the reduction
68 to tridiagonal form. If JOBZ = 'N', the array Q is not refer‐
69 enced.
70
71 LDQ (input) INTEGER
72 The leading dimension of the array Q. If JOBZ = 'V', then LDQ
73 >= max(1,N).
74
75 VL (input) DOUBLE PRECISION
76 VU (input) DOUBLE PRECISION If RANGE='V', the lower and
77 upper bounds of the interval to be searched for eigenvalues. VL
78 < VU. Not referenced if RANGE = 'A' or 'I'.
79
80 IL (input) INTEGER
81 IU (input) INTEGER If RANGE='I', the indices (in ascending
82 order) of the smallest and largest eigenvalues to be returned.
83 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0. Not
84 referenced if RANGE = 'A' or 'V'.
85
86 ABSTOL (input) DOUBLE PRECISION
87 The absolute error tolerance for the eigenvalues. An approxi‐
88 mate eigenvalue is accepted as converged when it is determined
89 to lie in an interval [a,b] of width less than or equal to
90 ABSTOL + EPS * max( |a|,|b| ) , where EPS is the machine pre‐
91 cision. If ABSTOL is less than or equal to zero, then EPS*|T|
92 will be used in its place, where |T| is the 1-norm of the
93 tridiagonal matrix obtained by reducing AB to tridiagonal form.
94 Eigenvalues will be computed most accurately when ABSTOL is set
95 to twice the underflow threshold 2*DLAMCH('S'), not zero. If
96 this routine returns with INFO>0, indicating that some eigen‐
97 vectors did not converge, try setting ABSTOL to 2*DLAMCH('S').
98 See "Computing Small Singular Values of Bidiagonal Matrices
99 with Guaranteed High Relative Accuracy," by Demmel and Kahan,
100 LAPACK Working Note #3.
101
102 M (output) INTEGER
103 The total number of eigenvalues found. 0 <= M <= N. If RANGE
104 = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
105
106 W (output) DOUBLE PRECISION array, dimension (N)
107 The first M elements contain the selected eigenvalues in
108 ascending order.
109
110 Z (output) COMPLEX*16 array, dimension (LDZ, max(1,M))
111 If JOBZ = 'V', then if INFO = 0, the first M columns of Z con‐
112 tain the orthonormal eigenvectors of the matrix A corresponding
113 to the selected eigenvalues, with the i-th column of Z holding
114 the eigenvector associated with W(i). If an eigenvector fails
115 to converge, then that column of Z contains the latest approxi‐
116 mation to the eigenvector, and the index of the eigenvector is
117 returned in IFAIL. If JOBZ = 'N', then Z is not referenced.
118 Note: the user must ensure that at least max(1,M) columns are
119 supplied in the array Z; if RANGE = 'V', the exact value of M
120 is not known in advance and an upper bound must be used.
121
122 LDZ (input) INTEGER
123 The leading dimension of the array Z. LDZ >= 1, and if JOBZ =
124 'V', LDZ >= max(1,N).
125
126 WORK (workspace) COMPLEX*16 array, dimension (N)
127
128 RWORK (workspace) DOUBLE PRECISION array, dimension (7*N)
129
130 IWORK (workspace) INTEGER array, dimension (5*N)
131
132 IFAIL (output) INTEGER array, dimension (N)
133 If JOBZ = 'V', then if INFO = 0, the first M elements of IFAIL
134 are zero. If INFO > 0, then IFAIL contains the indices of the
135 eigenvectors that failed to converge. If JOBZ = 'N', then
136 IFAIL is not referenced.
137
138 INFO (output) INTEGER
139 = 0: successful exit
140 < 0: if INFO = -i, the i-th argument had an illegal value
141 > 0: if INFO = i, then i eigenvectors failed to converge.
142 Their indices are stored in array IFAIL.
143
144
145
146 LAPACK driver routine (version 3.N2o)vember 2008 ZHBEVX(1)