LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sstevx.f
Go to the documentation of this file.
1 *> \brief <b> SSTEVX 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 SSTEVX + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sstevx.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sstevx.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sstevx.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SSTEVX( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL,
22 * M, W, Z, LDZ, WORK, IWORK, IFAIL, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER JOBZ, RANGE
26 * INTEGER IL, INFO, IU, LDZ, M, N
27 * REAL ABSTOL, VL, VU
28 * ..
29 * .. Array Arguments ..
30 * INTEGER IFAIL( * ), IWORK( * )
31 * REAL D( * ), E( * ), W( * ), WORK( * ), Z( LDZ, * )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *>
40 *> SSTEVX computes selected eigenvalues and, optionally, eigenvectors
41 *> of a real symmetric tridiagonal matrix A. Eigenvalues and
42 *> eigenvectors can be selected by specifying either a range of values
43 *> or a range of indices for the desired eigenvalues.
44 *> \endverbatim
45 *
46 * Arguments:
47 * ==========
48 *
49 *> \param[in] JOBZ
50 *> \verbatim
51 *> JOBZ is CHARACTER*1
52 *> = 'N': Compute eigenvalues only;
53 *> = 'V': Compute eigenvalues and eigenvectors.
54 *> \endverbatim
55 *>
56 *> \param[in] RANGE
57 *> \verbatim
58 *> RANGE is CHARACTER*1
59 *> = 'A': all eigenvalues will be found.
60 *> = 'V': all eigenvalues in the half-open interval (VL,VU]
61 *> will be found.
62 *> = 'I': the IL-th through IU-th eigenvalues will be found.
63 *> \endverbatim
64 *>
65 *> \param[in] N
66 *> \verbatim
67 *> N is INTEGER
68 *> The order of the matrix. N >= 0.
69 *> \endverbatim
70 *>
71 *> \param[in,out] D
72 *> \verbatim
73 *> D is REAL array, dimension (N)
74 *> On entry, the n diagonal elements of the tridiagonal matrix
75 *> A.
76 *> On exit, D may be multiplied by a constant factor chosen
77 *> to avoid over/underflow in computing the eigenvalues.
78 *> \endverbatim
79 *>
80 *> \param[in,out] E
81 *> \verbatim
82 *> E is REAL array, dimension (max(1,N-1))
83 *> On entry, the (n-1) subdiagonal elements of the tridiagonal
84 *> matrix A in elements 1 to N-1 of E.
85 *> On exit, E may be multiplied by a constant factor chosen
86 *> to avoid over/underflow in computing the eigenvalues.
87 *> \endverbatim
88 *>
89 *> \param[in] VL
90 *> \verbatim
91 *> VL is REAL
92 *> If RANGE='V', the lower bound of the interval to
93 *> be searched for eigenvalues. VL < VU.
94 *> Not referenced if RANGE = 'A' or 'I'.
95 *> \endverbatim
96 *>
97 *> \param[in] VU
98 *> \verbatim
99 *> VU is REAL
100 *> If RANGE='V', the upper bound of the interval to
101 *> be searched for eigenvalues. VL < VU.
102 *> Not referenced if RANGE = 'A' or 'I'.
103 *> \endverbatim
104 *>
105 *> \param[in] IL
106 *> \verbatim
107 *> IL is INTEGER
108 *> If RANGE='I', the index of the
109 *> smallest eigenvalue to be returned.
110 *> 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
111 *> Not referenced if RANGE = 'A' or 'V'.
112 *> \endverbatim
113 *>
114 *> \param[in] IU
115 *> \verbatim
116 *> IU is INTEGER
117 *> If RANGE='I', the index of the
118 *> largest eigenvalue to be returned.
119 *> 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
120 *> Not referenced if RANGE = 'A' or 'V'.
121 *> \endverbatim
122 *>
123 *> \param[in] ABSTOL
124 *> \verbatim
125 *> ABSTOL is REAL
126 *> The absolute error tolerance for the eigenvalues.
127 *> An approximate eigenvalue is accepted as converged
128 *> when it is determined to lie in an interval [a,b]
129 *> of width less than or equal to
130 *>
131 *> ABSTOL + EPS * max( |a|,|b| ) ,
132 *>
133 *> where EPS is the machine precision. If ABSTOL is less
134 *> than or equal to zero, then EPS*|T| will be used in
135 *> its place, where |T| is the 1-norm of the tridiagonal
136 *> matrix.
137 *>
138 *> Eigenvalues will be computed most accurately when ABSTOL is
139 *> set to twice the underflow threshold 2*SLAMCH('S'), not zero.
140 *> If this routine returns with INFO>0, indicating that some
141 *> eigenvectors did not converge, try setting ABSTOL to
142 *> 2*SLAMCH('S').
143 *>
144 *> See "Computing Small Singular Values of Bidiagonal Matrices
145 *> with Guaranteed High Relative Accuracy," by Demmel and
146 *> Kahan, LAPACK Working Note #3.
147 *> \endverbatim
148 *>
149 *> \param[out] M
150 *> \verbatim
151 *> M is INTEGER
152 *> The total number of eigenvalues found. 0 <= M <= N.
153 *> If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
154 *> \endverbatim
155 *>
156 *> \param[out] W
157 *> \verbatim
158 *> W is REAL array, dimension (N)
159 *> The first M elements contain the selected eigenvalues in
160 *> ascending order.
161 *> \endverbatim
162 *>
163 *> \param[out] Z
164 *> \verbatim
165 *> Z is REAL array, dimension (LDZ, max(1,M) )
166 *> If JOBZ = 'V', then if INFO = 0, the first M columns of Z
167 *> contain the orthonormal eigenvectors of the matrix A
168 *> corresponding to the selected eigenvalues, with the i-th
169 *> column of Z holding the eigenvector associated with W(i).
170 *> If an eigenvector fails to converge (INFO > 0), then that
171 *> column of Z contains the latest approximation to the
172 *> eigenvector, and the index of the eigenvector is returned
173 *> in IFAIL. If JOBZ = 'N', then Z is not referenced.
174 *> Note: the user must ensure that at least max(1,M) columns are
175 *> supplied in the array Z; if RANGE = 'V', the exact value of M
176 *> is not known in advance and an upper bound must be used.
177 *> \endverbatim
178 *>
179 *> \param[in] LDZ
180 *> \verbatim
181 *> LDZ is INTEGER
182 *> The leading dimension of the array Z. LDZ >= 1, and if
183 *> JOBZ = 'V', LDZ >= max(1,N).
184 *> \endverbatim
185 *>
186 *> \param[out] WORK
187 *> \verbatim
188 *> WORK is REAL array, dimension (5*N)
189 *> \endverbatim
190 *>
191 *> \param[out] IWORK
192 *> \verbatim
193 *> IWORK is INTEGER array, dimension (5*N)
194 *> \endverbatim
195 *>
196 *> \param[out] IFAIL
197 *> \verbatim
198 *> IFAIL is INTEGER array, dimension (N)
199 *> If JOBZ = 'V', then if INFO = 0, the first M elements of
200 *> IFAIL are zero. If INFO > 0, then IFAIL contains the
201 *> indices of the eigenvectors that failed to converge.
202 *> If JOBZ = 'N', then IFAIL is not referenced.
203 *> \endverbatim
204 *>
205 *> \param[out] INFO
206 *> \verbatim
207 *> INFO is INTEGER
208 *> = 0: successful exit
209 *> < 0: if INFO = -i, the i-th argument had an illegal value
210 *> > 0: if INFO = i, then i eigenvectors failed to converge.
211 *> Their indices are stored in array IFAIL.
212 *> \endverbatim
213 *
214 * Authors:
215 * ========
216 *
217 *> \author Univ. of Tennessee
218 *> \author Univ. of California Berkeley
219 *> \author Univ. of Colorado Denver
220 *> \author NAG Ltd.
221 *
222 *> \date June 2016
223 *
224 *> \ingroup realOTHEReigen
225 *
226 * =====================================================================
227  SUBROUTINE sstevx( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL,
228  $ m, w, z, ldz, work, iwork, ifail, info )
229 *
230 * -- LAPACK driver routine (version 3.6.1) --
231 * -- LAPACK is a software package provided by Univ. of Tennessee, --
232 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
233 * June 2016
234 *
235 * .. Scalar Arguments ..
236  CHARACTER JOBZ, RANGE
237  INTEGER IL, INFO, IU, LDZ, M, N
238  REAL ABSTOL, VL, VU
239 * ..
240 * .. Array Arguments ..
241  INTEGER IFAIL( * ), IWORK( * )
242  REAL D( * ), E( * ), W( * ), WORK( * ), Z( ldz, * )
243 * ..
244 *
245 * =====================================================================
246 *
247 * .. Parameters ..
248  REAL ZERO, ONE
249  parameter ( zero = 0.0e0, one = 1.0e0 )
250 * ..
251 * .. Local Scalars ..
252  LOGICAL ALLEIG, INDEIG, TEST, VALEIG, WANTZ
253  CHARACTER ORDER
254  INTEGER I, IMAX, INDIBL, INDISP, INDIWO, INDWRK,
255  $ iscale, itmp1, j, jj, nsplit
256  REAL BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA, SMLNUM,
257  $ tmp1, tnrm, vll, vuu
258 * ..
259 * .. External Functions ..
260  LOGICAL LSAME
261  REAL SLAMCH, SLANST
262  EXTERNAL lsame, slamch, slanst
263 * ..
264 * .. External Subroutines ..
265  EXTERNAL scopy, sscal, sstebz, sstein, ssteqr, ssterf,
266  $ sswap, xerbla
267 * ..
268 * .. Intrinsic Functions ..
269  INTRINSIC max, min, sqrt
270 * ..
271 * .. Executable Statements ..
272 *
273 * Test the input parameters.
274 *
275  wantz = lsame( jobz, 'V' )
276  alleig = lsame( range, 'A' )
277  valeig = lsame( range, 'V' )
278  indeig = lsame( range, 'I' )
279 *
280  info = 0
281  IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
282  info = -1
283  ELSE IF( .NOT.( alleig .OR. valeig .OR. indeig ) ) THEN
284  info = -2
285  ELSE IF( n.LT.0 ) THEN
286  info = -3
287  ELSE
288  IF( valeig ) THEN
289  IF( n.GT.0 .AND. vu.LE.vl )
290  $ info = -7
291  ELSE IF( indeig ) THEN
292  IF( il.LT.1 .OR. il.GT.max( 1, n ) ) THEN
293  info = -8
294  ELSE IF( iu.LT.min( n, il ) .OR. iu.GT.n ) THEN
295  info = -9
296  END IF
297  END IF
298  END IF
299  IF( info.EQ.0 ) THEN
300  IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) )
301  $ info = -14
302  END IF
303 *
304  IF( info.NE.0 ) THEN
305  CALL xerbla( 'SSTEVX', -info )
306  RETURN
307  END IF
308 *
309 * Quick return if possible
310 *
311  m = 0
312  IF( n.EQ.0 )
313  $ RETURN
314 *
315  IF( n.EQ.1 ) THEN
316  IF( alleig .OR. indeig ) THEN
317  m = 1
318  w( 1 ) = d( 1 )
319  ELSE
320  IF( vl.LT.d( 1 ) .AND. vu.GE.d( 1 ) ) THEN
321  m = 1
322  w( 1 ) = d( 1 )
323  END IF
324  END IF
325  IF( wantz )
326  $ z( 1, 1 ) = one
327  RETURN
328  END IF
329 *
330 * Get machine constants.
331 *
332  safmin = slamch( 'Safe minimum' )
333  eps = slamch( 'Precision' )
334  smlnum = safmin / eps
335  bignum = one / smlnum
336  rmin = sqrt( smlnum )
337  rmax = min( sqrt( bignum ), one / sqrt( sqrt( safmin ) ) )
338 *
339 * Scale matrix to allowable range, if necessary.
340 *
341  iscale = 0
342  IF ( valeig ) THEN
343  vll = vl
344  vuu = vu
345  ELSE
346  vll = zero
347  vuu = zero
348  ENDIF
349  tnrm = slanst( 'M', n, d, e )
350  IF( tnrm.GT.zero .AND. tnrm.LT.rmin ) THEN
351  iscale = 1
352  sigma = rmin / tnrm
353  ELSE IF( tnrm.GT.rmax ) THEN
354  iscale = 1
355  sigma = rmax / tnrm
356  END IF
357  IF( iscale.EQ.1 ) THEN
358  CALL sscal( n, sigma, d, 1 )
359  CALL sscal( n-1, sigma, e( 1 ), 1 )
360  IF( valeig ) THEN
361  vll = vl*sigma
362  vuu = vu*sigma
363  END IF
364  END IF
365 *
366 * If all eigenvalues are desired and ABSTOL is less than zero, then
367 * call SSTERF or SSTEQR. If this fails for some eigenvalue, then
368 * try SSTEBZ.
369 *
370  test = .false.
371  IF( indeig ) THEN
372  IF( il.EQ.1 .AND. iu.EQ.n ) THEN
373  test = .true.
374  END IF
375  END IF
376  IF( ( alleig .OR. test ) .AND. ( abstol.LE.zero ) ) THEN
377  CALL scopy( n, d, 1, w, 1 )
378  CALL scopy( n-1, e( 1 ), 1, work( 1 ), 1 )
379  indwrk = n + 1
380  IF( .NOT.wantz ) THEN
381  CALL ssterf( n, w, work, info )
382  ELSE
383  CALL ssteqr( 'I', n, w, work, z, ldz, work( indwrk ), info )
384  IF( info.EQ.0 ) THEN
385  DO 10 i = 1, n
386  ifail( i ) = 0
387  10 CONTINUE
388  END IF
389  END IF
390  IF( info.EQ.0 ) THEN
391  m = n
392  GO TO 20
393  END IF
394  info = 0
395  END IF
396 *
397 * Otherwise, call SSTEBZ and, if eigenvectors are desired, SSTEIN.
398 *
399  IF( wantz ) THEN
400  order = 'B'
401  ELSE
402  order = 'E'
403  END IF
404  indwrk = 1
405  indibl = 1
406  indisp = indibl + n
407  indiwo = indisp + n
408  CALL sstebz( range, order, n, vll, vuu, il, iu, abstol, d, e, m,
409  $ nsplit, w, iwork( indibl ), iwork( indisp ),
410  $ work( indwrk ), iwork( indiwo ), info )
411 *
412  IF( wantz ) THEN
413  CALL sstein( n, d, e, m, w, iwork( indibl ), iwork( indisp ),
414  $ z, ldz, work( indwrk ), iwork( indiwo ), ifail,
415  $ info )
416  END IF
417 *
418 * If matrix was scaled, then rescale eigenvalues appropriately.
419 *
420  20 CONTINUE
421  IF( iscale.EQ.1 ) THEN
422  IF( info.EQ.0 ) THEN
423  imax = m
424  ELSE
425  imax = info - 1
426  END IF
427  CALL sscal( imax, one / sigma, w, 1 )
428  END IF
429 *
430 * If eigenvalues are not in order, then sort them, along with
431 * eigenvectors.
432 *
433  IF( wantz ) THEN
434  DO 40 j = 1, m - 1
435  i = 0
436  tmp1 = w( j )
437  DO 30 jj = j + 1, m
438  IF( w( jj ).LT.tmp1 ) THEN
439  i = jj
440  tmp1 = w( jj )
441  END IF
442  30 CONTINUE
443 *
444  IF( i.NE.0 ) THEN
445  itmp1 = iwork( indibl+i-1 )
446  w( i ) = w( j )
447  iwork( indibl+i-1 ) = iwork( indibl+j-1 )
448  w( j ) = tmp1
449  iwork( indibl+j-1 ) = itmp1
450  CALL sswap( n, z( 1, i ), 1, z( 1, j ), 1 )
451  IF( info.NE.0 ) THEN
452  itmp1 = ifail( i )
453  ifail( i ) = ifail( j )
454  ifail( j ) = itmp1
455  END IF
456  END IF
457  40 CONTINUE
458  END IF
459 *
460  RETURN
461 *
462 * End of SSTEVX
463 *
464  END
subroutine sstebz(RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E, M, NSPLIT, W, IBLOCK, ISPLIT, WORK, IWORK, INFO)
SSTEBZ
Definition: sstebz.f:275
subroutine sstein(N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, IWORK, IFAIL, INFO)
SSTEIN
Definition: sstein.f:176
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine ssteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
SSTEQR
Definition: ssteqr.f:133
subroutine sstevx(JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, IWORK, IFAIL, INFO)
SSTEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matric...
Definition: sstevx.f:229
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
subroutine sswap(N, SX, INCX, SY, INCY)
SSWAP
Definition: sswap.f:53
subroutine ssterf(N, D, E, INFO)
SSTERF
Definition: ssterf.f:88
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:53