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