1DSYEVR(1) LAPACK driver routine (version 3.1) DSYEVR(1)
2
3
4
6 DSYEVR - selected eigenvalues and, optionally, eigenvectors of a real
7 symmetric matrix A
8
10 SUBROUTINE DSYEVR( JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
11 ABSTOL, M, W, Z, LDZ, ISUPPZ, WORK, LWORK, IWORK,
12 LIWORK, INFO )
13
14 CHARACTER JOBZ, RANGE, UPLO
15
16 INTEGER IL, INFO, IU, LDA, LDZ, LIWORK, LWORK, M, N
17
18 DOUBLE PRECISION ABSTOL, VL, VU
19
20 INTEGER ISUPPZ( * ), IWORK( * )
21
22 DOUBLE PRECISION A( LDA, * ), W( * ), WORK( * ), Z( LDZ, *
23 )
24
26 DSYEVR computes selected eigenvalues and, optionally, eigenvectors of a
27 real symmetric matrix A. Eigenvalues and eigenvectors can be selected
28 by specifying either a range of values or a range of indices for the
29 desired eigenvalues.
30
31 DSYEVR first reduces the matrix A to tridiagonal form T with a call to
32 DSYTRD. Then, whenever possible, DSYEVR calls DSTEMR to compute the
33 eigenspectrum using Relatively Robust Representations. DSTEMR computes
34 eigenvalues by the dqds algorithm, while orthogonal eigenvectors are
35 computed from various "good" L D L^T representations (also known as
36 Relatively Robust Representations). Gram-Schmidt orthogonalization is
37 avoided as far as possible. More specifically, the various steps of the
38 algorithm are as follows.
39
40 For each unreduced block (submatrix) of T,
41 (a) Compute T - sigma I = L D L^T, so that L and D
42 define all the wanted eigenvalues to high relative accuracy.
43 This means that small relative changes in the entries of D and L
44 cause only small relative changes in the eigenvalues and
45 eigenvectors. The standard (unfactored) representation of the
46 tridiagonal matrix T does not have this property in general.
47 (b) Compute the eigenvalues to suitable accuracy.
48 If the eigenvectors are desired, the algorithm attains full
49 accuracy of the computed eigenvalues only right before
50 the corresponding vectors have to be computed, see steps c) and
51 d).
52 (c) For each cluster of close eigenvalues, select a new
53 shift close to the cluster, find a new factorization, and refine
54 the shifted eigenvalues to suitable accuracy.
55 (d) For each eigenvalue with a large enough relative separation com‐
56 pute
57 the corresponding eigenvector by forming a rank revealing
58 twisted
59 factorization. Go back to (c) for any clusters that remain.
60
61 The desired accuracy of the output can be specified by the input param‐
62 eter ABSTOL.
63
64 For more details, see DSTEMR's documentation and:
65 - Inderjit S. Dhillon and Beresford N. Parlett: "Multiple representa‐
66 tions
67 to compute orthogonal eigenvectors of symmetric tridiagonal matri‐
68 ces,"
69 Linear Algebra and its Applications, 387(1), pp. 1-28, August 2004.
70 - Inderjit Dhillon and Beresford Parlett: "Orthogonal Eigenvectors and
71 Relative Gaps," SIAM Journal on Matrix Analysis and Applications,
72 Vol. 25,
73 2004. Also LAPACK Working Note 154.
74 - Inderjit Dhillon: "A new O(n^2) algorithm for the symmetric
75 tridiagonal eigenvalue/eigenvector problem",
76 Computer Science Division Technical Report No. UCB/CSD-97-971,
77 UC Berkeley, May 1997.
78
79
80 Note 1 : DSYEVR calls DSTEMR when the full spectrum is requested on
81 machines which conform to the ieee-754 floating point standard. DSYEVR
82 calls DSTEBZ and SSTEIN on non-ieee machines and
83 when partial spectrum requests are made.
84
85 Normal execution of DSTEMR may create NaNs and infinities and hence may
86 abort due to a floating point exception in environments which do not
87 handle NaNs and infinities in the ieee standard default manner.
88
89
91 JOBZ (input) CHARACTER*1
92 = 'N': Compute eigenvalues only;
93 = 'V': Compute eigenvalues and eigenvectors.
94
95 RANGE (input) CHARACTER*1
96 = 'A': all eigenvalues will be found.
97 = 'V': all eigenvalues in the half-open interval (VL,VU] will
98 be found. = 'I': the IL-th through IU-th eigenvalues will be
99 found.
100
101 UPLO (input) CHARACTER*1
102 = 'U': Upper triangle of A is stored;
103 = 'L': Lower triangle of A is stored.
104
105 N (input) INTEGER
106 The order of the matrix A. N >= 0.
107
108 A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
109 On entry, the symmetric matrix A. If UPLO = 'U', the leading
110 N-by-N upper triangular part of A contains the upper triangular
111 part of the matrix A. If UPLO = 'L', the leading N-by-N lower
112 triangular part of A contains the lower triangular part of the
113 matrix A. On exit, the lower triangle (if UPLO='L') or the
114 upper triangle (if UPLO='U') of A, including the diagonal, is
115 destroyed.
116
117 LDA (input) INTEGER
118 The leading dimension of the array A. LDA >= max(1,N).
119
120 VL (input) DOUBLE PRECISION
121 VU (input) DOUBLE PRECISION If RANGE='V', the lower and
122 upper bounds of the interval to be searched for eigenvalues. VL
123 < VU. Not referenced if RANGE = 'A' or 'I'.
124
125 IL (input) INTEGER
126 IU (input) INTEGER If RANGE='I', the indices (in ascending
127 order) of the smallest and largest eigenvalues to be returned.
128 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0. Not
129 referenced if RANGE = 'A' or 'V'.
130
131 ABSTOL (input) DOUBLE PRECISION
132 The absolute error tolerance for the eigenvalues. An approxi‐
133 mate eigenvalue is accepted as converged when it is determined
134 to lie in an interval [a,b] of width less than or equal to
135
136 ABSTOL + EPS * max( |a|,|b| ) ,
137
138 where EPS is the machine precision. If ABSTOL is less than or
139 equal to zero, then EPS*|T| will be used in its place, where
140 |T| is the 1-norm of the tridiagonal matrix obtained by reduc‐
141 ing A to tridiagonal form.
142
143 See "Computing Small Singular Values of Bidiagonal Matrices
144 with Guaranteed High Relative Accuracy," by Demmel and Kahan,
145 LAPACK Working Note #3.
146
147 If high relative accuracy is important, set ABSTOL to DLAMCH(
148 'Safe minimum' ). Doing so will guarantee that eigenvalues are
149 computed to high relative accuracy when possible in future
150 releases. The current code does not make any guarantees about
151 high relative accuracy, but future releases will. See J. Barlow
152 and J. Demmel, "Computing Accurate Eigensystems of Scaled Diag‐
153 onally Dominant Matrices", LAPACK Working Note #7, for a dis‐
154 cussion of which matrices define their eigenvalues to high rel‐
155 ative accuracy.
156
157 M (output) INTEGER
158 The total number of eigenvalues found. 0 <= M <= N. If RANGE
159 = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
160
161 W (output) DOUBLE PRECISION array, dimension (N)
162 The first M elements contain the selected eigenvalues in
163 ascending order.
164
165 Z (output) DOUBLE PRECISION array, dimension (LDZ, max(1,M))
166 If JOBZ = 'V', then if INFO = 0, the first M columns of Z con‐
167 tain the orthonormal eigenvectors of the matrix A corresponding
168 to the selected eigenvalues, with the i-th column of Z holding
169 the eigenvector associated with W(i). If JOBZ = 'N', then Z is
170 not referenced. Note: the user must ensure that at least
171 max(1,M) columns are supplied in the array Z; if RANGE = 'V',
172 the exact value of M is not known in advance and an upper bound
173 must be used. Supplying N columns is always safe.
174
175 LDZ (input) INTEGER
176 The leading dimension of the array Z. LDZ >= 1, and if JOBZ =
177 'V', LDZ >= max(1,N).
178
179 ISUPPZ (output) INTEGER array, dimension ( 2*max(1,M) )
180 The support of the eigenvectors in Z, i.e., the indices indi‐
181 cating the nonzero elements in Z. The i-th eigenvector is
182 nonzero only in elements ISUPPZ( 2*i-1 ) through ISUPPZ( 2*i ).
183
184 WORK (workspace/output) DOUBLE PRECISION array, dimension
185 (MAX(1,LWORK))
186 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
187
188 LWORK (input) INTEGER
189 The dimension of the array WORK. LWORK >= max(1,26*N). For
190 optimal efficiency, LWORK >= (NB+6)*N, where NB is the max of
191 the blocksize for DSYTRD and DORMTR returned by ILAENV.
192
193 If LWORK = -1, then a workspace query is assumed; the routine
194 only calculates the optimal size of the WORK array, returns
195 this value as the first entry of the WORK array, and no error
196 message related to LWORK is issued by XERBLA.
197
198 IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
199 On exit, if INFO = 0, IWORK(1) returns the optimal LWORK.
200
201 LIWORK (input) INTEGER
202 The dimension of the array IWORK. LIWORK >= max(1,10*N).
203
204 If LIWORK = -1, then a workspace query is assumed; the routine
205 only calculates the optimal size of the IWORK array, returns
206 this value as the first entry of the IWORK array, and no error
207 message related to LIWORK is issued by XERBLA.
208
209 INFO (output) INTEGER
210 = 0: successful exit
211 < 0: if INFO = -i, the i-th argument had an illegal value
212 > 0: Internal error
213
215 Based on contributions by
216 Inderjit Dhillon, IBM Almaden, USA
217 Osni Marques, LBNL/NERSC, USA
218 Ken Stanley, Computer Science Division, University of
219 California at Berkeley, USA
220 Jason Riedy, Computer Science Division, University of
221 California at Berkeley, USA
222
223
224
225
226 LAPACK driver routine (version 3.N1o)vember 2006 DSYEVR(1)