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