1 *> \brief <b> DSPEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices</b>
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DSPEV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dspev.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dspev.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dspev.f">
21 * SUBROUTINE DSPEV( JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO )
23 * .. Scalar Arguments ..
24 * CHARACTER JOBZ, UPLO
25 * INTEGER INFO, LDZ, N
27 * .. Array Arguments ..
28 * DOUBLE PRECISION AP( * ), W( * ), WORK( * ), Z( LDZ, * )
37 *> DSPEV computes all the eigenvalues and, optionally, eigenvectors of a
38 *> real symmetric matrix A in packed storage.
46 *> JOBZ is CHARACTER*1
47 *> = 'N': Compute eigenvalues only;
48 *> = 'V': Compute eigenvalues and eigenvectors.
53 *> UPLO is CHARACTER*1
54 *> = 'U': Upper triangle of A is stored;
55 *> = 'L': Lower triangle of A is stored.
61 *> The order of the matrix A. N >= 0.
66 *> AP is DOUBLE PRECISION array, dimension (N*(N+1)/2)
67 *> On entry, the upper or lower triangle of the symmetric matrix
68 *> A, packed columnwise in a linear array. The j-th column of A
69 *> is stored in the array AP as follows:
70 *> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
71 *> if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
73 *> On exit, AP is overwritten by values generated during the
74 *> reduction to tridiagonal form. If UPLO = 'U', the diagonal
75 *> and first superdiagonal of the tridiagonal matrix T overwrite
76 *> the corresponding elements of A, and if UPLO = 'L', the
77 *> diagonal and first subdiagonal of T overwrite the
78 *> corresponding elements of A.
83 *> W is DOUBLE PRECISION array, dimension (N)
84 *> If INFO = 0, the eigenvalues in ascending order.
89 *> Z is DOUBLE PRECISION array, dimension (LDZ, N)
90 *> If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal
91 *> eigenvectors of the matrix A, with the i-th column of Z
92 *> holding the eigenvector associated with W(i).
93 *> If JOBZ = 'N', then Z is not referenced.
99 *> The leading dimension of the array Z. LDZ >= 1, and if
100 *> JOBZ = 'V', LDZ >= max(1,N).
105 *> WORK is DOUBLE PRECISION array, dimension (3*N)
111 *> = 0: successful exit.
112 *> < 0: if INFO = -i, the i-th argument had an illegal value.
113 *> > 0: if INFO = i, the algorithm failed to converge; i
114 *> off-diagonal elements of an intermediate tridiagonal
115 *> form did not converge to zero.
121 *> \author Univ. of Tennessee
122 *> \author Univ. of California Berkeley
123 *> \author Univ. of Colorado Denver
126 *> \date November 2011
128 *> \ingroup doubleOTHEReigen
130 * =====================================================================
131 SUBROUTINE DSPEV( JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, INFO )
133 * -- LAPACK driver routine (version 3.4.0) --
134 * -- LAPACK is a software package provided by Univ. of Tennessee, --
135 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
138 * .. Scalar Arguments ..
142 * .. Array Arguments ..
143 DOUBLE PRECISION AP( * ), W( * ), WORK( * ), Z( LDZ, * )
146 * =====================================================================
149 DOUBLE PRECISION ZERO, ONE
150 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
152 * .. Local Scalars ..
154 INTEGER IINFO, IMAX, INDE, INDTAU, INDWRK, ISCALE
155 DOUBLE PRECISION ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA,
158 * .. External Functions ..
160 DOUBLE PRECISION DLAMCH, DLANSP
161 EXTERNAL LSAME, DLAMCH, DLANSP
163 * .. External Subroutines ..
164 EXTERNAL DOPGTR, DSCAL, DSPTRD, DSTEQR, DSTERF, XERBLA
166 * .. Intrinsic Functions ..
169 * .. Executable Statements ..
171 * Test the input parameters.
173 WANTZ = LSAME( JOBZ, 'V' )
176 IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
178 ELSE IF( .NOT.( LSAME( UPLO, 'U' ) .OR. LSAME( UPLO, 'L' ) ) )
181 ELSE IF( N.LT.0 ) THEN
183 ELSE IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
188 CALL XERBLA( 'DSPEV ', -INFO )
192 * Quick return if possible
204 * Get machine constants.
206 SAFMIN = DLAMCH( 'Safe minimum' )
207 EPS = DLAMCH( 'Precision' )
208 SMLNUM = SAFMIN / EPS
209 BIGNUM = ONE / SMLNUM
210 RMIN = SQRT( SMLNUM )
211 RMAX = SQRT( BIGNUM )
213 * Scale matrix to allowable range, if necessary.
215 ANRM = DLANSP( 'M', UPLO, N, AP, WORK )
217 IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
220 ELSE IF( ANRM.GT.RMAX ) THEN
224 IF( ISCALE.EQ.1 ) THEN
225 CALL DSCAL( ( N*( N+1 ) ) / 2, SIGMA, AP, 1 )
228 * Call DSPTRD to reduce symmetric packed matrix to tridiagonal form.
232 CALL DSPTRD( UPLO, N, AP, W, WORK( INDE ), WORK( INDTAU ), IINFO )
234 * For eigenvalues only, call DSTERF. For eigenvectors, first call
235 * DOPGTR to generate the orthogonal matrix, then call DSTEQR.
237 IF( .NOT.WANTZ ) THEN
238 CALL DSTERF( N, W, WORK( INDE ), INFO )
241 CALL DOPGTR( UPLO, N, AP, WORK( INDTAU ), Z, LDZ,
242 $ WORK( INDWRK ), IINFO )
243 CALL DSTEQR( JOBZ, N, W, WORK( INDE ), Z, LDZ, WORK( INDTAU ),
247 * If matrix was scaled, then rescale eigenvalues appropriately.
249 IF( ISCALE.EQ.1 ) THEN
255 CALL DSCAL( IMAX, ONE / SIGMA, W, 1 )