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