LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sstev.f
Go to the documentation of this file.
1*> \brief <b> SSTEV 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*> Download SSTEV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sstev.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sstev.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sstev.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SSTEV( JOBZ, N, D, E, Z, LDZ, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER JOBZ
23* INTEGER INFO, LDZ, N
24* ..
25* .. Array Arguments ..
26* REAL D( * ), E( * ), WORK( * ), Z( LDZ, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> SSTEV computes all eigenvalues and, optionally, eigenvectors of a
36*> real symmetric tridiagonal matrix A.
37*> \endverbatim
38*
39* Arguments:
40* ==========
41*
42*> \param[in] JOBZ
43*> \verbatim
44*> JOBZ is CHARACTER*1
45*> = 'N': Compute eigenvalues only;
46*> = 'V': Compute eigenvalues and eigenvectors.
47*> \endverbatim
48*>
49*> \param[in] N
50*> \verbatim
51*> N is INTEGER
52*> The order of the matrix. N >= 0.
53*> \endverbatim
54*>
55*> \param[in,out] D
56*> \verbatim
57*> D is REAL array, dimension (N)
58*> On entry, the n diagonal elements of the tridiagonal matrix
59*> A.
60*> On exit, if INFO = 0, the eigenvalues in ascending order.
61*> \endverbatim
62*>
63*> \param[in,out] E
64*> \verbatim
65*> E is REAL array, dimension (N-1)
66*> On entry, the (n-1) subdiagonal elements of the tridiagonal
67*> matrix A, stored in elements 1 to N-1 of E.
68*> On exit, the contents of E are destroyed.
69*> \endverbatim
70*>
71*> \param[out] Z
72*> \verbatim
73*> Z is REAL array, dimension (LDZ, N)
74*> If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal
75*> eigenvectors of the matrix A, with the i-th column of Z
76*> holding the eigenvector associated with D(i).
77*> If JOBZ = 'N', then Z is not referenced.
78*> \endverbatim
79*>
80*> \param[in] LDZ
81*> \verbatim
82*> LDZ is INTEGER
83*> The leading dimension of the array Z. LDZ >= 1, and if
84*> JOBZ = 'V', LDZ >= max(1,N).
85*> \endverbatim
86*>
87*> \param[out] WORK
88*> \verbatim
89*> WORK is REAL array, dimension (max(1,2*N-2))
90*> If JOBZ = 'N', WORK is not referenced.
91*> \endverbatim
92*>
93*> \param[out] INFO
94*> \verbatim
95*> INFO is INTEGER
96*> = 0: successful exit
97*> < 0: if INFO = -i, the i-th argument had an illegal value
98*> > 0: if INFO = i, the algorithm failed to converge; i
99*> off-diagonal elements of E did not converge to zero.
100*> \endverbatim
101*
102* Authors:
103* ========
104*
105*> \author Univ. of Tennessee
106*> \author Univ. of California Berkeley
107*> \author Univ. of Colorado Denver
108*> \author NAG Ltd.
109*
110*> \ingroup stev
111*
112* =====================================================================
113 SUBROUTINE sstev( JOBZ, N, D, E, Z, LDZ, WORK, INFO )
114*
115* -- LAPACK driver routine --
116* -- LAPACK is a software package provided by Univ. of Tennessee, --
117* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
118*
119* .. Scalar Arguments ..
120 CHARACTER JOBZ
121 INTEGER INFO, LDZ, N
122* ..
123* .. Array Arguments ..
124 REAL D( * ), E( * ), WORK( * ), Z( LDZ, * )
125* ..
126*
127* =====================================================================
128*
129* .. Parameters ..
130 REAL ZERO, ONE
131 parameter( zero = 0.0e0, one = 1.0e0 )
132* ..
133* .. Local Scalars ..
134 LOGICAL WANTZ
135 INTEGER IMAX, ISCALE
136 REAL BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA, SMLNUM,
137 $ TNRM
138* ..
139* .. External Functions ..
140 LOGICAL LSAME
141 REAL SLAMCH, SLANST
142 EXTERNAL lsame, slamch, slanst
143* ..
144* .. External Subroutines ..
145 EXTERNAL sscal, ssteqr, ssterf, xerbla
146* ..
147* .. Intrinsic Functions ..
148 INTRINSIC sqrt
149* ..
150* .. Executable Statements ..
151*
152* Test the input parameters.
153*
154 wantz = lsame( jobz, 'V' )
155*
156 info = 0
157 IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
158 info = -1
159 ELSE IF( n.LT.0 ) THEN
160 info = -2
161 ELSE IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
162 info = -6
163 END IF
164*
165 IF( info.NE.0 ) THEN
166 CALL xerbla( 'SSTEV ', -info )
167 RETURN
168 END IF
169*
170* Quick return if possible
171*
172 IF( n.EQ.0 )
173 $ RETURN
174*
175 IF( n.EQ.1 ) THEN
176 IF( wantz )
177 $ z( 1, 1 ) = one
178 RETURN
179 END IF
180*
181* Get machine constants.
182*
183 safmin = slamch( 'Safe minimum' )
184 eps = slamch( 'Precision' )
185 smlnum = safmin / eps
186 bignum = one / smlnum
187 rmin = sqrt( smlnum )
188 rmax = sqrt( bignum )
189*
190* Scale matrix to allowable range, if necessary.
191*
192 iscale = 0
193 tnrm = slanst( 'M', n, d, e )
194 IF( tnrm.GT.zero .AND. tnrm.LT.rmin ) THEN
195 iscale = 1
196 sigma = rmin / tnrm
197 ELSE IF( tnrm.GT.rmax ) THEN
198 iscale = 1
199 sigma = rmax / tnrm
200 END IF
201 IF( iscale.EQ.1 ) THEN
202 CALL sscal( n, sigma, d, 1 )
203 CALL sscal( n-1, sigma, e( 1 ), 1 )
204 END IF
205*
206* For eigenvalues only, call SSTERF. For eigenvalues and
207* eigenvectors, call SSTEQR.
208*
209 IF( .NOT.wantz ) THEN
210 CALL ssterf( n, d, e, info )
211 ELSE
212 CALL ssteqr( 'I', n, d, e, z, ldz, work, info )
213 END IF
214*
215* If matrix was scaled, then rescale eigenvalues appropriately.
216*
217 IF( iscale.EQ.1 ) THEN
218 IF( info.EQ.0 ) THEN
219 imax = n
220 ELSE
221 imax = info - 1
222 END IF
223 CALL sscal( imax, one / sigma, d, 1 )
224 END IF
225*
226 RETURN
227*
228* End of SSTEV
229*
230 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine ssteqr(compz, n, d, e, z, ldz, work, info)
SSTEQR
Definition ssteqr.f:129
subroutine ssterf(n, d, e, info)
SSTERF
Definition ssterf.f:84
subroutine sstev(jobz, n, d, e, z, ldz, work, info)
SSTEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices
Definition sstev.f:114