1*> \brief <b> DSYEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY 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 DSYEV + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsyev.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsyev.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsyev.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE DSYEV_NSRT( JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, INFO )
22*
23*       .. Scalar Arguments ..
24*       CHARACTER          JOBZ, UPLO
25*       INTEGER            INFO, LDA, LWORK, N
26*       ..
27*       .. Array Arguments ..
28*       DOUBLE PRECISION   A( LDA, * ), W( * ), WORK( * )
29*       ..
30*
31*
32*> \par Purpose:
33*  =============
34*>
35*> \verbatim
36*>
37*> DSYEV computes all eigenvalues and, optionally, eigenvectors of a
38*> real symmetric 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] UPLO
52*> \verbatim
53*>          UPLO is CHARACTER*1
54*>          = 'U':  Upper triangle of A is stored;
55*>          = 'L':  Lower triangle of A is stored.
56*> \endverbatim
57*>
58*> \param[in] N
59*> \verbatim
60*>          N is INTEGER
61*>          The order of the matrix A.  N >= 0.
62*> \endverbatim
63*>
64*> \param[in,out] A
65*> \verbatim
66*>          A is DOUBLE PRECISION array, dimension (LDA, N)
67*>          On entry, the symmetric matrix A.  If UPLO = 'U', the
68*>          leading N-by-N upper triangular part of A contains the
69*>          upper triangular part of the matrix A.  If UPLO = 'L',
70*>          the leading N-by-N lower triangular part of A contains
71*>          the lower triangular part of the matrix A.
72*>          On exit, if JOBZ = 'V', then if INFO = 0, A contains the
73*>          orthonormal eigenvectors of the matrix A.
74*>          If JOBZ = 'N', then on exit the lower triangle (if UPLO='L')
75*>          or the upper triangle (if UPLO='U') of A, including the
76*>          diagonal, is destroyed.
77*> \endverbatim
78*>
79*> \param[in] LDA
80*> \verbatim
81*>          LDA is INTEGER
82*>          The leading dimension of the array A.  LDA >= max(1,N).
83*> \endverbatim
84*>
85*> \param[out] W
86*> \verbatim
87*>          W is DOUBLE PRECISION array, dimension (N)
88*>          If INFO = 0, the eigenvalues but not sorted
89*> \endverbatim
90*>
91*> \param[out] WORK
92*> \verbatim
93*>          WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
94*>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
95*> \endverbatim
96*>
97*> \param[in] LWORK
98*> \verbatim
99*>          LWORK is INTEGER
100*>          The length of the array WORK.  LWORK >= max(1,3*N-1).
101*>          For optimal efficiency, LWORK >= (NB+2)*N,
102*>          where NB is the blocksize for DSYTRD returned by ILAENV.
103*>
104*>          If LWORK = -1, then a workspace query is assumed; the routine
105*>          only calculates the optimal size of the WORK array, returns
106*>          this value as the first entry of the WORK array, and no error
107*>          message related to LWORK is issued by XERBLA.
108*> \endverbatim
109*>
110*> \param[out] INFO
111*> \verbatim
112*>          INFO is INTEGER
113*>          = 0:  successful exit
114*>          < 0:  if INFO = -i, the i-th argument had an illegal value
115*>          > 0:  if INFO = i, the algorithm failed to converge; i
116*>                off-diagonal elements of an intermediate tridiagonal
117*>                form did not converge to zero.
118*> \endverbatim
119*
120*  Authors:
121*  ========
122*
123*> \author Univ. of Tennessee
124*> \author Univ. of California Berkeley
125*> \author Univ. of Colorado Denver
126*> \author NAG Ltd.
127*
128*> \date November 2011
129*
130*> \ingroup doubleSYeigen
131*
132*  =====================================================================
133      SUBROUTINE DSYEV_NSRT( JOBZ, UPLO, N, A, LDA, W, WORK, LWORK,
134     +                       INFO )
135*
136*  -- LAPACK driver routine (version 3.4.0) --
137*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
138*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
139*     November 2011
140*
141*     .. Scalar Arguments ..
142      CHARACTER          JOBZ, UPLO
143      INTEGER            INFO, LDA, LWORK, N
144*     ..
145*     .. Array Arguments ..
146      DOUBLE PRECISION   A( LDA, * ), W( * ), WORK( * )
147*     ..
148*
149*  =====================================================================
150*
151*     .. Parameters ..
152      DOUBLE PRECISION   ZERO, ONE
153      PARAMETER          ( ZERO = 0.0D0, ONE = 1.0D0 )
154*     ..
155*     .. Local Scalars ..
156      LOGICAL            LOWER, LQUERY, WANTZ
157      INTEGER            IINFO, IMAX, INDE, INDTAU, INDWRK, ISCALE,
158     $                   LLWORK, LWKOPT, NB
159      DOUBLE PRECISION   ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA,
160     $                   SMLNUM
161*     ..
162*     .. External Functions ..
163      LOGICAL            LSAME
164      INTEGER            ILAENV
165      DOUBLE PRECISION   DLAMCH, DLANSY
166      EXTERNAL           LSAME, ILAENV, DLAMCH, DLANSY
167*     ..
168*     .. External Subroutines ..
169      EXTERNAL           DLASCL, DORGTR, DSCAL, DSTEQR, DSTERF, DSYTRD,
170     $                   XERBLA
171*     ..
172*     .. Intrinsic Functions ..
173      INTRINSIC          MAX, SQRT
174*     ..
175*     .. Executable Statements ..
176*
177*     Test the input parameters.
178*
179      WANTZ = LSAME( JOBZ, 'V' )
180      LOWER = LSAME( UPLO, 'L' )
181      LQUERY = ( LWORK.EQ.-1 )
182*
183      INFO = 0
184      IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
185         INFO = -1
186      ELSE IF( .NOT.( LOWER .OR. LSAME( UPLO, 'U' ) ) ) THEN
187         INFO = -2
188      ELSE IF( N.LT.0 ) THEN
189         INFO = -3
190      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
191         INFO = -5
192      END IF
193*
194      IF( INFO.EQ.0 ) THEN
195         NB = ILAENV( 1, 'DSYTRD', UPLO, N, -1, -1, -1 )
196         LWKOPT = MAX( 1, ( NB+2 )*N )
197         WORK( 1 ) = LWKOPT
198*
199         IF( LWORK.LT.MAX( 1, 3*N-1 ) .AND. .NOT.LQUERY )
200     $      INFO = -8
201      END IF
202*
203      IF( INFO.NE.0 ) THEN
204         CALL XERBLA( 'DSYEV ', -INFO )
205         RETURN
206      ELSE IF( LQUERY ) THEN
207         RETURN
208      END IF
209*
210*     Quick return if possible
211*
212      IF( N.EQ.0 ) THEN
213         RETURN
214      END IF
215*
216      IF( N.EQ.1 ) THEN
217         W( 1 ) = A( 1, 1 )
218         WORK( 1 ) = 2
219         IF( WANTZ )
220     $      A( 1, 1 ) = ONE
221         RETURN
222      END IF
223*
224*     Get machine constants.
225*
226      SAFMIN = DLAMCH( 'Safe minimum' )
227      EPS = DLAMCH( 'Precision' )
228      SMLNUM = SAFMIN / EPS
229      BIGNUM = ONE / SMLNUM
230      RMIN = SQRT( SMLNUM )
231      RMAX = SQRT( BIGNUM )
232*
233*     Scale matrix to allowable range, if necessary.
234*
235      ANRM = DLANSY( 'M', UPLO, N, A, LDA, WORK )
236      ISCALE = 0
237      IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
238         ISCALE = 1
239         SIGMA = RMIN / ANRM
240      ELSE IF( ANRM.GT.RMAX ) THEN
241         ISCALE = 1
242         SIGMA = RMAX / ANRM
243      END IF
244      IF( ISCALE.EQ.1 )
245     $   CALL DLASCL( UPLO, 0, 0, ONE, SIGMA, N, N, A, LDA, INFO )
246*
247*     Call DSYTRD to reduce symmetric matrix to tridiagonal form.
248*
249      INDE = 1
250      INDTAU = INDE + N
251      INDWRK = INDTAU + N
252      LLWORK = LWORK - INDWRK + 1
253      CALL DSYTRD( UPLO, N, A, LDA, W, WORK( INDE ), WORK( INDTAU ),
254     $             WORK( INDWRK ), LLWORK, IINFO )
255*
256*     For eigenvalues only, call DSTERF.  For eigenvectors, first call
257*     DORGTR to generate the orthogonal matrix, then call DSTEQR.
258*
259      IF( .NOT.WANTZ ) THEN
260         CALL DSTERF_NSRT( N, W, WORK( INDE ), INFO )
261      ELSE
262         CALL DORGTR( UPLO, N, A, LDA, WORK( INDTAU ), WORK( INDWRK ),
263     $                LLWORK, IINFO )
264         CALL DSTEQR_NSRT( JOBZ, N, W, WORK( INDE ), A, LDA,
265     $                     WORK( INDTAU ), INFO )
266      END IF
267*
268*     If matrix was scaled, then rescale eigenvalues appropriately.
269*
270      IF( ISCALE.EQ.1 ) THEN
271         IF( INFO.EQ.0 ) THEN
272            IMAX = N
273         ELSE
274            IMAX = INFO - 1
275         END IF
276         CALL DSCAL( IMAX, ONE / SIGMA, W, 1 )
277      END IF
278*
279*     Set WORK(1) to optimal workspace size.
280*
281      WORK( 1 ) = LWKOPT
282*
283      RETURN
284*
285*     End of DSYEV
286*
287      END
288c $Id: dsyev.f 24343 2013-06-22 05:35:15Z d3y133 $
289