LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sstevd()

subroutine sstevd ( character jobz,
integer n,
real, dimension( * ) d,
real, dimension( * ) e,
real, dimension( ldz, * ) z,
integer ldz,
real, dimension( * ) work,
integer lwork,
integer, dimension( * ) iwork,
integer liwork,
integer info )

SSTEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices

Download SSTEVD + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> SSTEVD computes all eigenvalues and, optionally, eigenvectors of a
!> real symmetric tridiagonal matrix. If eigenvectors are desired, it
!> uses a divide and conquer algorithm.
!>
!> 
Parameters
[in]JOBZ
!>          JOBZ is CHARACTER*1
!>          = 'N':  Compute eigenvalues only;
!>          = 'V':  Compute eigenvalues and eigenvectors.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix.  N >= 0.
!> 
[in,out]D
!>          D is REAL array, dimension (N)
!>          On entry, the n diagonal elements of the tridiagonal matrix
!>          A.
!>          On exit, if INFO = 0, the eigenvalues in ascending order.
!> 
[in,out]E
!>          E is REAL array, dimension (N-1)
!>          On entry, the (n-1) subdiagonal elements of the tridiagonal
!>          matrix A, stored in elements 1 to N-1 of E.
!>          On exit, the contents of E are destroyed.
!> 
[out]Z
!>          Z is REAL array, dimension (LDZ, N)
!>          If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal
!>          eigenvectors of the matrix A, with the i-th column of Z
!>          holding the eigenvector associated with D(i).
!>          If JOBZ = 'N', then Z is not referenced.
!> 
[in]LDZ
!>          LDZ is INTEGER
!>          The leading dimension of the array Z.  LDZ >= 1, and if
!>          JOBZ = 'V', LDZ >= max(1,N).
!> 
[out]WORK
!>          WORK is REAL array,
!>                                         dimension (LWORK)
!>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The dimension of the array WORK.
!>          If JOBZ  = 'N' or N <= 1 then LWORK must be at least 1.
!>          If JOBZ  = 'V' and N > 1 then LWORK must be at least
!>                         ( 1 + 4*N + N**2 ).
!>
!>          If LWORK = -1, then a workspace query is assumed; the routine
!>          only calculates the optimal sizes of the WORK and IWORK
!>          arrays, returns these values as the first entries of the WORK
!>          and IWORK arrays, and no error message related to LWORK or
!>          LIWORK is issued by XERBLA.
!> 
[out]IWORK
!>          IWORK is INTEGER array, dimension (MAX(1,LIWORK))
!>          On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
!> 
[in]LIWORK
!>          LIWORK is INTEGER
!>          The dimension of the array IWORK.
!>          If JOBZ  = 'N' or N <= 1 then LIWORK must be at least 1.
!>          If JOBZ  = 'V' and N > 1 then LIWORK must be at least 3+5*N.
!>
!>          If LIWORK = -1, then a workspace query is assumed; the
!>          routine only calculates the optimal sizes of the WORK and
!>          IWORK arrays, returns these values as the first entries of
!>          the WORK and IWORK arrays, and no error message related to
!>          LWORK or LIWORK is issued by XERBLA.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!>          > 0:  if INFO = i, the algorithm failed to converge; i
!>                off-diagonal elements of E did not converge to zero.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 153 of file sstevd.f.

155*
156* -- LAPACK driver routine --
157* -- LAPACK is a software package provided by Univ. of Tennessee, --
158* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
159*
160* .. Scalar Arguments ..
161 CHARACTER JOBZ
162 INTEGER INFO, LDZ, LIWORK, LWORK, N
163* ..
164* .. Array Arguments ..
165 INTEGER IWORK( * )
166 REAL D( * ), E( * ), WORK( * ), Z( LDZ, * )
167* ..
168*
169* =====================================================================
170*
171* .. Parameters ..
172 REAL ZERO, ONE
173 parameter( zero = 0.0e0, one = 1.0e0 )
174* ..
175* .. Local Scalars ..
176 LOGICAL LQUERY, WANTZ
177 INTEGER ISCALE, LIWMIN, LWMIN
178 REAL BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA, SMLNUM,
179 $ TNRM
180* ..
181* .. External Functions ..
182 LOGICAL LSAME
183 REAL SLAMCH, SLANST, SROUNDUP_LWORK
184 EXTERNAL lsame, slamch, slanst,
186* ..
187* .. External Subroutines ..
188 EXTERNAL sscal, sstedc, ssterf, xerbla
189* ..
190* .. Intrinsic Functions ..
191 INTRINSIC sqrt
192* ..
193* .. Executable Statements ..
194*
195* Test the input parameters.
196*
197 wantz = lsame( jobz, 'V' )
198 lquery = ( lwork.EQ.-1 .OR. liwork.EQ.-1 )
199*
200 info = 0
201 liwmin = 1
202 lwmin = 1
203 IF( n.GT.1 .AND. wantz ) THEN
204 lwmin = 1 + 4*n + n**2
205 liwmin = 3 + 5*n
206 END IF
207*
208 IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
209 info = -1
210 ELSE IF( n.LT.0 ) THEN
211 info = -2
212 ELSE IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
213 info = -6
214 END IF
215*
216 IF( info.EQ.0 ) THEN
217 work( 1 ) = sroundup_lwork(lwmin)
218 iwork( 1 ) = liwmin
219*
220 IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
221 info = -8
222 ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) THEN
223 info = -10
224 END IF
225 END IF
226*
227 IF( info.NE.0 ) THEN
228 CALL xerbla( 'SSTEVD', -info )
229 RETURN
230 ELSE IF( lquery ) THEN
231 RETURN
232 END IF
233*
234* Quick return if possible
235*
236 IF( n.EQ.0 )
237 $ RETURN
238*
239 IF( n.EQ.1 ) THEN
240 IF( wantz )
241 $ z( 1, 1 ) = one
242 RETURN
243 END IF
244*
245* Get machine constants.
246*
247 safmin = slamch( 'Safe minimum' )
248 eps = slamch( 'Precision' )
249 smlnum = safmin / eps
250 bignum = one / smlnum
251 rmin = sqrt( smlnum )
252 rmax = sqrt( bignum )
253*
254* Scale matrix to allowable range, if necessary.
255*
256 iscale = 0
257 tnrm = slanst( 'M', n, d, e )
258 IF( tnrm.GT.zero .AND. tnrm.LT.rmin ) THEN
259 iscale = 1
260 sigma = rmin / tnrm
261 ELSE IF( tnrm.GT.rmax ) THEN
262 iscale = 1
263 sigma = rmax / tnrm
264 END IF
265 IF( iscale.EQ.1 ) THEN
266 CALL sscal( n, sigma, d, 1 )
267 CALL sscal( n-1, sigma, e( 1 ), 1 )
268 END IF
269*
270* For eigenvalues only, call SSTERF. For eigenvalues and
271* eigenvectors, call SSTEDC.
272*
273 IF( .NOT.wantz ) THEN
274 CALL ssterf( n, d, e, info )
275 ELSE
276 CALL sstedc( 'I', n, d, e, z, ldz, work, lwork, iwork,
277 $ liwork,
278 $ info )
279 END IF
280*
281* If matrix was scaled, then rescale eigenvalues appropriately.
282*
283 IF( iscale.EQ.1 )
284 $ CALL sscal( n, one / sigma, d, 1 )
285*
286 work( 1 ) = sroundup_lwork(lwmin)
287 iwork( 1 ) = liwmin
288*
289 RETURN
290*
291* End of SSTEVD
292*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function slanst(norm, n, d, e)
SLANST returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition slanst.f:98
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine sstedc(compz, n, d, e, z, ldz, work, lwork, iwork, liwork, info)
SSTEDC
Definition sstedc.f:180
subroutine ssterf(n, d, e, info)
SSTERF
Definition ssterf.f:84
Here is the call graph for this function:
Here is the caller graph for this function: