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