LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
sstevr.f
Go to the documentation of this file.
1 *> \brief <b> SSTEVR computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices</b>
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SSTEVR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sstevr.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sstevr.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sstevr.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SSTEVR( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL,
22 * M, W, Z, LDZ, ISUPPZ, WORK, LWORK, IWORK,
23 * LIWORK, INFO )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER JOBZ, RANGE
27 * INTEGER IL, INFO, IU, LDZ, LIWORK, LWORK, M, N
28 * REAL ABSTOL, VL, VU
29 * ..
30 * .. Array Arguments ..
31 * INTEGER ISUPPZ( * ), IWORK( * )
32 * REAL D( * ), E( * ), W( * ), WORK( * ), Z( LDZ, * )
33 * ..
34 *
35 *
36 *> \par Purpose:
37 * =============
38 *>
39 *> \verbatim
40 *>
41 *> SSTEVR computes selected eigenvalues and, optionally, eigenvectors
42 *> of a real symmetric tridiagonal matrix T. Eigenvalues and
43 *> eigenvectors can be selected by specifying either a range of values
44 *> or a range of indices for the desired eigenvalues.
45 *>
46 *> Whenever possible, SSTEVR calls SSTEMR to compute the
47 *> eigenspectrum using Relatively Robust Representations. SSTEMR
48 *> computes eigenvalues by the dqds algorithm, while orthogonal
49 *> eigenvectors are computed from various "good" L D L^T representations
50 *> (also known as Relatively Robust Representations). Gram-Schmidt
51 *> orthogonalization is avoided as far as possible. More specifically,
52 *> the various steps of the algorithm are as follows. For the i-th
53 *> unreduced block of T,
54 *> (a) Compute T - sigma_i = L_i D_i L_i^T, such that L_i D_i L_i^T
55 *> is a relatively robust representation,
56 *> (b) Compute the eigenvalues, lambda_j, of L_i D_i L_i^T to high
57 *> relative accuracy by the dqds algorithm,
58 *> (c) If there is a cluster of close eigenvalues, "choose" sigma_i
59 *> close to the cluster, and go to step (a),
60 *> (d) Given the approximate eigenvalue lambda_j of L_i D_i L_i^T,
61 *> compute the corresponding eigenvector by forming a
62 *> rank-revealing twisted factorization.
63 *> The desired accuracy of the output can be specified by the input
64 *> parameter ABSTOL.
65 *>
66 *> For more details, see "A new O(n^2) algorithm for the symmetric
67 *> tridiagonal eigenvalue/eigenvector problem", by Inderjit Dhillon,
68 *> Computer Science Division Technical Report No. UCB//CSD-97-971,
69 *> UC Berkeley, May 1997.
70 *>
71 *>
72 *> Note 1 : SSTEVR calls SSTEMR when the full spectrum is requested
73 *> on machines which conform to the ieee-754 floating point standard.
74 *> SSTEVR calls SSTEBZ and SSTEIN on non-ieee machines and
75 *> when partial spectrum requests are made.
76 *>
77 *> Normal execution of SSTEMR may create NaNs and infinities and
78 *> hence may abort due to a floating point exception in environments
79 *> which do not handle NaNs and infinities in the ieee standard default
80 *> manner.
81 *> \endverbatim
82 *
83 * Arguments:
84 * ==========
85 *
86 *> \param[in] JOBZ
87 *> \verbatim
88 *> JOBZ is CHARACTER*1
89 *> = 'N': Compute eigenvalues only;
90 *> = 'V': Compute eigenvalues and eigenvectors.
91 *> \endverbatim
92 *>
93 *> \param[in] RANGE
94 *> \verbatim
95 *> RANGE is CHARACTER*1
96 *> = 'A': all eigenvalues will be found.
97 *> = 'V': all eigenvalues in the half-open interval (VL,VU]
98 *> will be found.
99 *> = 'I': the IL-th through IU-th eigenvalues will be found.
100 *> For RANGE = 'V' or 'I' and IU - IL < N - 1, SSTEBZ and
101 *> SSTEIN are called
102 *> \endverbatim
103 *>
104 *> \param[in] N
105 *> \verbatim
106 *> N is INTEGER
107 *> The order of the matrix. N >= 0.
108 *> \endverbatim
109 *>
110 *> \param[in,out] D
111 *> \verbatim
112 *> D is REAL array, dimension (N)
113 *> On entry, the n diagonal elements of the tridiagonal matrix
114 *> A.
115 *> On exit, D may be multiplied by a constant factor chosen
116 *> to avoid over/underflow in computing the eigenvalues.
117 *> \endverbatim
118 *>
119 *> \param[in,out] E
120 *> \verbatim
121 *> E is REAL array, dimension (max(1,N-1))
122 *> On entry, the (n-1) subdiagonal elements of the tridiagonal
123 *> matrix A in elements 1 to N-1 of E.
124 *> On exit, E may be multiplied by a constant factor chosen
125 *> to avoid over/underflow in computing the eigenvalues.
126 *> \endverbatim
127 *>
128 *> \param[in] VL
129 *> \verbatim
130 *> VL is REAL
131 *> \endverbatim
132 *>
133 *> \param[in] VU
134 *> \verbatim
135 *> VU is REAL
136 *> If RANGE='V', the lower and upper bounds of the interval to
137 *> be searched for eigenvalues. VL < VU.
138 *> Not referenced if RANGE = 'A' or 'I'.
139 *> \endverbatim
140 *>
141 *> \param[in] IL
142 *> \verbatim
143 *> IL is INTEGER
144 *> \endverbatim
145 *>
146 *> \param[in] IU
147 *> \verbatim
148 *> IU is INTEGER
149 *> If RANGE='I', the indices (in ascending order) of the
150 *> smallest and largest eigenvalues to be returned.
151 *> 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
152 *> Not referenced if RANGE = 'A' or 'V'.
153 *> \endverbatim
154 *>
155 *> \param[in] ABSTOL
156 *> \verbatim
157 *> ABSTOL is REAL
158 *> The absolute error tolerance for the eigenvalues.
159 *> An approximate eigenvalue is accepted as converged
160 *> when it is determined to lie in an interval [a,b]
161 *> of width less than or equal to
162 *>
163 *> ABSTOL + EPS * max( |a|,|b| ) ,
164 *>
165 *> where EPS is the machine precision. If ABSTOL is less than
166 *> or equal to zero, then EPS*|T| will be used in its place,
167 *> where |T| is the 1-norm of the tridiagonal matrix obtained
168 *> by reducing A to tridiagonal form.
169 *>
170 *> See "Computing Small Singular Values of Bidiagonal Matrices
171 *> with Guaranteed High Relative Accuracy," by Demmel and
172 *> Kahan, LAPACK Working Note #3.
173 *>
174 *> If high relative accuracy is important, set ABSTOL to
175 *> SLAMCH( 'Safe minimum' ). Doing so will guarantee that
176 *> eigenvalues are computed to high relative accuracy when
177 *> possible in future releases. The current code does not
178 *> make any guarantees about high relative accuracy, but
179 *> future releases will. See J. Barlow and J. Demmel,
180 *> "Computing Accurate Eigensystems of Scaled Diagonally
181 *> Dominant Matrices", LAPACK Working Note #7, for a discussion
182 *> of which matrices define their eigenvalues to high relative
183 *> accuracy.
184 *> \endverbatim
185 *>
186 *> \param[out] M
187 *> \verbatim
188 *> M is INTEGER
189 *> The total number of eigenvalues found. 0 <= M <= N.
190 *> If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
191 *> \endverbatim
192 *>
193 *> \param[out] W
194 *> \verbatim
195 *> W is REAL array, dimension (N)
196 *> The first M elements contain the selected eigenvalues in
197 *> ascending order.
198 *> \endverbatim
199 *>
200 *> \param[out] Z
201 *> \verbatim
202 *> Z is REAL array, dimension (LDZ, max(1,M) )
203 *> If JOBZ = 'V', then if INFO = 0, the first M columns of Z
204 *> contain the orthonormal eigenvectors of the matrix A
205 *> corresponding to the selected eigenvalues, with the i-th
206 *> column of Z holding the eigenvector associated with W(i).
207 *> Note: the user must ensure that at least max(1,M) columns are
208 *> supplied in the array Z; if RANGE = 'V', the exact value of M
209 *> is not known in advance and an upper bound must be used.
210 *> \endverbatim
211 *>
212 *> \param[in] LDZ
213 *> \verbatim
214 *> LDZ is INTEGER
215 *> The leading dimension of the array Z. LDZ >= 1, and if
216 *> JOBZ = 'V', LDZ >= max(1,N).
217 *> \endverbatim
218 *>
219 *> \param[out] ISUPPZ
220 *> \verbatim
221 *> ISUPPZ is INTEGER array, dimension ( 2*max(1,M) )
222 *> The support of the eigenvectors in Z, i.e., the indices
223 *> indicating the nonzero elements in Z. The i-th eigenvector
224 *> is nonzero only in elements ISUPPZ( 2*i-1 ) through
225 *> ISUPPZ( 2*i ).
226 *> Implemented only for RANGE = 'A' or 'I' and IU - IL = N - 1
227 *> \endverbatim
228 *>
229 *> \param[out] WORK
230 *> \verbatim
231 *> WORK is REAL array, dimension (MAX(1,LWORK))
232 *> On exit, if INFO = 0, WORK(1) returns the optimal (and
233 *> minimal) LWORK.
234 *> \endverbatim
235 *>
236 *> \param[in] LWORK
237 *> \verbatim
238 *> LWORK is INTEGER
239 *> The dimension of the array WORK. LWORK >= 20*N.
240 *>
241 *> If LWORK = -1, then a workspace query is assumed; the routine
242 *> only calculates the optimal sizes of the WORK and IWORK
243 *> arrays, returns these values as the first entries of the WORK
244 *> and IWORK arrays, and no error message related to LWORK or
245 *> LIWORK is issued by XERBLA.
246 *> \endverbatim
247 *>
248 *> \param[out] IWORK
249 *> \verbatim
250 *> IWORK is INTEGER array, dimension (MAX(1,LIWORK))
251 *> On exit, if INFO = 0, IWORK(1) returns the optimal (and
252 *> minimal) LIWORK.
253 *> \endverbatim
254 *>
255 *> \param[in] LIWORK
256 *> \verbatim
257 *> LIWORK is INTEGER
258 *> The dimension of the array IWORK. LIWORK >= 10*N.
259 *>
260 *> If LIWORK = -1, then a workspace query is assumed; the
261 *> routine only calculates the optimal sizes of the WORK and
262 *> IWORK arrays, returns these values as the first entries of
263 *> the WORK and IWORK arrays, and no error message related to
264 *> LWORK or LIWORK is issued by XERBLA.
265 *> \endverbatim
266 *>
267 *> \param[out] INFO
268 *> \verbatim
269 *> INFO is INTEGER
270 *> = 0: successful exit
271 *> < 0: if INFO = -i, the i-th argument had an illegal value
272 *> > 0: Internal error
273 *> \endverbatim
274 *
275 * Authors:
276 * ========
277 *
278 *> \author Univ. of Tennessee
279 *> \author Univ. of California Berkeley
280 *> \author Univ. of Colorado Denver
281 *> \author NAG Ltd.
282 *
283 *> \date November 2011
284 *
285 *> \ingroup realOTHEReigen
286 *
287 *> \par Contributors:
288 * ==================
289 *>
290 *> Inderjit Dhillon, IBM Almaden, USA \n
291 *> Osni Marques, LBNL/NERSC, USA \n
292 *> Ken Stanley, Computer Science Division, University of
293 *> California at Berkeley, USA \n
294 *> Jason Riedy, Computer Science Division, University of
295 *> California at Berkeley, USA \n
296 *>
297 * =====================================================================
298  SUBROUTINE sstevr( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL,
299  $ m, w, z, ldz, isuppz, work, lwork, iwork,
300  $ liwork, info )
301 *
302 * -- LAPACK driver routine (version 3.4.0) --
303 * -- LAPACK is a software package provided by Univ. of Tennessee, --
304 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
305 * November 2011
306 *
307 * .. Scalar Arguments ..
308  CHARACTER jobz, range
309  INTEGER il, info, iu, ldz, liwork, lwork, m, n
310  REAL abstol, vl, vu
311 * ..
312 * .. Array Arguments ..
313  INTEGER isuppz( * ), iwork( * )
314  REAL d( * ), e( * ), w( * ), work( * ), z( ldz, * )
315 * ..
316 *
317 * =====================================================================
318 *
319 * .. Parameters ..
320  REAL zero, one, two
321  parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
322 * ..
323 * .. Local Scalars ..
324  LOGICAL alleig, indeig, test, lquery, valeig, wantz,
325  $ tryrac
326  CHARACTER order
327  INTEGER i, ieeeok, imax, indibl, indifl, indisp,
328  $ indiwo, iscale, j, jj, liwmin, lwmin, nsplit
329  REAL bignum, eps, rmax, rmin, safmin, sigma, smlnum,
330  $ tmp1, tnrm, vll, vuu
331 * ..
332 * .. External Functions ..
333  LOGICAL lsame
334  INTEGER ilaenv
335  REAL slamch, slanst
336  EXTERNAL lsame, ilaenv, slamch, slanst
337 * ..
338 * .. External Subroutines ..
339  EXTERNAL scopy, sscal, sstebz, sstemr, sstein, ssterf,
340  $ sswap, xerbla
341 * ..
342 * .. Intrinsic Functions ..
343  INTRINSIC max, min, sqrt
344 * ..
345 * .. Executable Statements ..
346 *
347 *
348 * Test the input parameters.
349 *
350  ieeeok = ilaenv( 10, 'SSTEVR', 'N', 1, 2, 3, 4 )
351 *
352  wantz = lsame( jobz, 'V' )
353  alleig = lsame( range, 'A' )
354  valeig = lsame( range, 'V' )
355  indeig = lsame( range, 'I' )
356 *
357  lquery = ( ( lwork.EQ.-1 ) .OR. ( liwork.EQ.-1 ) )
358  lwmin = max( 1, 20*n )
359  liwmin = max(1, 10*n )
360 *
361 *
362  info = 0
363  IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
364  info = -1
365  ELSE IF( .NOT.( alleig .OR. valeig .OR. indeig ) ) THEN
366  info = -2
367  ELSE IF( n.LT.0 ) THEN
368  info = -3
369  ELSE
370  IF( valeig ) THEN
371  IF( n.GT.0 .AND. vu.LE.vl )
372  $ info = -7
373  ELSE IF( indeig ) THEN
374  IF( il.LT.1 .OR. il.GT.max( 1, n ) ) THEN
375  info = -8
376  ELSE IF( iu.LT.min( n, il ) .OR. iu.GT.n ) THEN
377  info = -9
378  END IF
379  END IF
380  END IF
381  IF( info.EQ.0 ) THEN
382  IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
383  info = -14
384  END IF
385  END IF
386 *
387  IF( info.EQ.0 ) THEN
388  work( 1 ) = lwmin
389  iwork( 1 ) = liwmin
390 *
391  IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
392  info = -17
393  ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) THEN
394  info = -19
395  END IF
396  END IF
397 *
398  IF( info.NE.0 ) THEN
399  CALL xerbla( 'SSTEVR', -info )
400  return
401  ELSE IF( lquery ) THEN
402  return
403  END IF
404 *
405 * Quick return if possible
406 *
407  m = 0
408  IF( n.EQ.0 )
409  $ return
410 *
411  IF( n.EQ.1 ) THEN
412  IF( alleig .OR. indeig ) THEN
413  m = 1
414  w( 1 ) = d( 1 )
415  ELSE
416  IF( vl.LT.d( 1 ) .AND. vu.GE.d( 1 ) ) THEN
417  m = 1
418  w( 1 ) = d( 1 )
419  END IF
420  END IF
421  IF( wantz )
422  $ z( 1, 1 ) = one
423  return
424  END IF
425 *
426 * Get machine constants.
427 *
428  safmin = slamch( 'Safe minimum' )
429  eps = slamch( 'Precision' )
430  smlnum = safmin / eps
431  bignum = one / smlnum
432  rmin = sqrt( smlnum )
433  rmax = min( sqrt( bignum ), one / sqrt( sqrt( safmin ) ) )
434 *
435 *
436 * Scale matrix to allowable range, if necessary.
437 *
438  iscale = 0
439  vll = vl
440  vuu = vu
441 *
442  tnrm = slanst( 'M', n, d, e )
443  IF( tnrm.GT.zero .AND. tnrm.LT.rmin ) THEN
444  iscale = 1
445  sigma = rmin / tnrm
446  ELSE IF( tnrm.GT.rmax ) THEN
447  iscale = 1
448  sigma = rmax / tnrm
449  END IF
450  IF( iscale.EQ.1 ) THEN
451  CALL sscal( n, sigma, d, 1 )
452  CALL sscal( n-1, sigma, e( 1 ), 1 )
453  IF( valeig ) THEN
454  vll = vl*sigma
455  vuu = vu*sigma
456  END IF
457  END IF
458 
459 * Initialize indices into workspaces. Note: These indices are used only
460 * if SSTERF or SSTEMR fail.
461 
462 * IWORK(INDIBL:INDIBL+M-1) corresponds to IBLOCK in SSTEBZ and
463 * stores the block indices of each of the M<=N eigenvalues.
464  indibl = 1
465 * IWORK(INDISP:INDISP+NSPLIT-1) corresponds to ISPLIT in SSTEBZ and
466 * stores the starting and finishing indices of each block.
467  indisp = indibl + n
468 * IWORK(INDIFL:INDIFL+N-1) stores the indices of eigenvectors
469 * that corresponding to eigenvectors that fail to converge in
470 * SSTEIN. This information is discarded; if any fail, the driver
471 * returns INFO > 0.
472  indifl = indisp + n
473 * INDIWO is the offset of the remaining integer workspace.
474  indiwo = indisp + n
475 *
476 * If all eigenvalues are desired, then
477 * call SSTERF or SSTEMR. If this fails for some eigenvalue, then
478 * try SSTEBZ.
479 *
480 *
481  test = .false.
482  IF( indeig ) THEN
483  IF( il.EQ.1 .AND. iu.EQ.n ) THEN
484  test = .true.
485  END IF
486  END IF
487  IF( ( alleig .OR. test ) .AND. ieeeok.EQ.1 ) THEN
488  CALL scopy( n-1, e( 1 ), 1, work( 1 ), 1 )
489  IF( .NOT.wantz ) THEN
490  CALL scopy( n, d, 1, w, 1 )
491  CALL ssterf( n, w, work, info )
492  ELSE
493  CALL scopy( n, d, 1, work( n+1 ), 1 )
494  IF (abstol .LE. two*n*eps) THEN
495  tryrac = .true.
496  ELSE
497  tryrac = .false.
498  END IF
499  CALL sstemr( jobz, 'A', n, work( n+1 ), work, vl, vu, il,
500  $ iu, m, w, z, ldz, n, isuppz, tryrac,
501  $ work( 2*n+1 ), lwork-2*n, iwork, liwork, info )
502 *
503  END IF
504  IF( info.EQ.0 ) THEN
505  m = n
506  go to 10
507  END IF
508  info = 0
509  END IF
510 *
511 * Otherwise, call SSTEBZ and, if eigenvectors are desired, SSTEIN.
512 *
513  IF( wantz ) THEN
514  order = 'B'
515  ELSE
516  order = 'E'
517  END IF
518 
519  CALL sstebz( range, order, n, vll, vuu, il, iu, abstol, d, e, m,
520  $ nsplit, w, iwork( indibl ), iwork( indisp ), work,
521  $ iwork( indiwo ), info )
522 *
523  IF( wantz ) THEN
524  CALL sstein( n, d, e, m, w, iwork( indibl ), iwork( indisp ),
525  $ z, ldz, work, iwork( indiwo ), iwork( indifl ),
526  $ info )
527  END IF
528 *
529 * If matrix was scaled, then rescale eigenvalues appropriately.
530 *
531  10 continue
532  IF( iscale.EQ.1 ) THEN
533  IF( info.EQ.0 ) THEN
534  imax = m
535  ELSE
536  imax = info - 1
537  END IF
538  CALL sscal( imax, one / sigma, w, 1 )
539  END IF
540 *
541 * If eigenvalues are not in order, then sort them, along with
542 * eigenvectors.
543 *
544  IF( wantz ) THEN
545  DO 30 j = 1, m - 1
546  i = 0
547  tmp1 = w( j )
548  DO 20 jj = j + 1, m
549  IF( w( jj ).LT.tmp1 ) THEN
550  i = jj
551  tmp1 = w( jj )
552  END IF
553  20 continue
554 *
555  IF( i.NE.0 ) THEN
556  w( i ) = w( j )
557  w( j ) = tmp1
558  CALL sswap( n, z( 1, i ), 1, z( 1, j ), 1 )
559  END IF
560  30 continue
561  END IF
562 *
563 * Causes problems with tests 19 & 20:
564 * IF (wantz .and. INDEIG ) Z( 1,1) = Z(1,1) / 1.002 + .002
565 *
566 *
567  work( 1 ) = lwmin
568  iwork( 1 ) = liwmin
569  return
570 *
571 * End of SSTEVR
572 *
573  END