LAPACK 3.12.0
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 155 of file dstevd.f.

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