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

◆ dstevd()

subroutine dstevd ( character jobz,
integer n,
double precision, dimension( * ) d,
double precision, dimension( * ) e,
double precision, dimension( ldz, * ) z,
integer ldz,
double precision, dimension( * ) work,
integer lwork,
integer, dimension( * ) iwork,
integer liwork,
integer info )

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

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

Purpose:
!>
!> DSTEVD 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 dstevd.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 DOUBLE PRECISION D( * ), E( * ), WORK( * ), Z( LDZ, * )
167* ..
168*
169* =====================================================================
170*
171* .. Parameters ..
172 DOUBLE PRECISION ZERO, ONE
173 parameter( zero = 0.0d0, one = 1.0d0 )
174* ..
175* .. Local Scalars ..
176 LOGICAL LQUERY, WANTZ
177 INTEGER ISCALE, LIWMIN, LWMIN
178 DOUBLE PRECISION BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA, SMLNUM,
179 $ TNRM
180* ..
181* .. External Functions ..
182 LOGICAL LSAME
183 DOUBLE PRECISION DLAMCH, DLANST
184 EXTERNAL lsame, dlamch, dlanst
185* ..
186* .. External Subroutines ..
187 EXTERNAL dscal, dstedc, dsterf, xerbla
188* ..
189* .. Intrinsic Functions ..
190 INTRINSIC sqrt
191* ..
192* .. Executable Statements ..
193*
194* Test the input parameters.
195*
196 wantz = lsame( jobz, 'V' )
197 lquery = ( lwork.EQ.-1 .OR. liwork.EQ.-1 )
198*
199 info = 0
200 liwmin = 1
201 lwmin = 1
202 IF( n.GT.1 .AND. wantz ) THEN
203 lwmin = 1 + 4*n + n**2
204 liwmin = 3 + 5*n
205 END IF
206*
207 IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
208 info = -1
209 ELSE IF( n.LT.0 ) THEN
210 info = -2
211 ELSE IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
212 info = -6
213 END IF
214*
215 IF( info.EQ.0 ) THEN
216 work( 1 ) = lwmin
217 iwork( 1 ) = liwmin
218*
219 IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
220 info = -8
221 ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) THEN
222 info = -10
223 END IF
224 END IF
225*
226 IF( info.NE.0 ) THEN
227 CALL xerbla( 'DSTEVD', -info )
228 RETURN
229 ELSE IF( lquery ) THEN
230 RETURN
231 END IF
232*
233* Quick return if possible
234*
235 IF( n.EQ.0 )
236 $ RETURN
237*
238 IF( n.EQ.1 ) THEN
239 IF( wantz )
240 $ z( 1, 1 ) = one
241 RETURN
242 END IF
243*
244* Get machine constants.
245*
246 safmin = dlamch( 'Safe minimum' )
247 eps = dlamch( 'Precision' )
248 smlnum = safmin / eps
249 bignum = one / smlnum
250 rmin = sqrt( smlnum )
251 rmax = sqrt( bignum )
252*
253* Scale matrix to allowable range, if necessary.
254*
255 iscale = 0
256 tnrm = dlanst( 'M', n, d, e )
257 IF( tnrm.GT.zero .AND. tnrm.LT.rmin ) THEN
258 iscale = 1
259 sigma = rmin / tnrm
260 ELSE IF( tnrm.GT.rmax ) THEN
261 iscale = 1
262 sigma = rmax / tnrm
263 END IF
264 IF( iscale.EQ.1 ) THEN
265 CALL dscal( n, sigma, d, 1 )
266 CALL dscal( n-1, sigma, e( 1 ), 1 )
267 END IF
268*
269* For eigenvalues only, call DSTERF. For eigenvalues and
270* eigenvectors, call DSTEDC.
271*
272 IF( .NOT.wantz ) THEN
273 CALL dsterf( n, d, e, info )
274 ELSE
275 CALL dstedc( 'I', n, d, e, z, ldz, work, lwork, iwork,
276 $ liwork,
277 $ info )
278 END IF
279*
280* If matrix was scaled, then rescale eigenvalues appropriately.
281*
282 IF( iscale.EQ.1 )
283 $ CALL dscal( n, one / sigma, d, 1 )
284*
285 work( 1 ) = lwmin
286 iwork( 1 ) = liwmin
287*
288 RETURN
289*
290* End of DSTEVD
291*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlanst(norm, n, d, e)
DLANST returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition dlanst.f:98
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
subroutine dstedc(compz, n, d, e, z, ldz, work, lwork, iwork, liwork, info)
DSTEDC
Definition dstedc.f:180
subroutine dsterf(n, d, e, info)
DSTERF
Definition dsterf.f:84
Here is the call graph for this function:
Here is the caller graph for this function: