5e783793162fad53f0637ac419891488b582e031
[platform/upstream/lapack.git] / SRC / ssyevd.f
1 *> \brief <b> SSYEVD 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 SSYEVD + dependencies 
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssyevd.f"> 
11 *> [TGZ]</a> 
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssyevd.f"> 
13 *> [ZIP]</a> 
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssyevd.f"> 
15 *> [TXT]</a>
16 *> \endhtmlonly 
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE SSYEVD( JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
22 *                          LIWORK, INFO )
23
24 *       .. Scalar Arguments ..
25 *       CHARACTER          JOBZ, UPLO
26 *       INTEGER            INFO, LDA, LIWORK, LWORK, N
27 *       ..
28 *       .. Array Arguments ..
29 *       INTEGER            IWORK( * )
30 *       REAL               A( LDA, * ), W( * ), WORK( * )
31 *       ..
32 *  
33 *
34 *> \par Purpose:
35 *  =============
36 *>
37 *> \verbatim
38 *>
39 *> SSYEVD computes all eigenvalues and, optionally, eigenvectors of a
40 *> real symmetric matrix A. If eigenvectors are desired, it uses a
41 *> divide and conquer algorithm.
42 *>
43 *> The divide and conquer algorithm makes very mild assumptions about
44 *> floating point arithmetic. It will work on machines with a guard
45 *> digit in add/subtract, or on those binary machines without guard
46 *> digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or
47 *> Cray-2. It could conceivably fail on hexadecimal or decimal machines
48 *> without guard digits, but we know of none.
49 *>
50 *> Because of large use of BLAS of level 3, SSYEVD needs N**2 more
51 *> workspace than SSYEVX.
52 *> \endverbatim
53 *
54 *  Arguments:
55 *  ==========
56 *
57 *> \param[in] JOBZ
58 *> \verbatim
59 *>          JOBZ is CHARACTER*1
60 *>          = 'N':  Compute eigenvalues only;
61 *>          = 'V':  Compute eigenvalues and eigenvectors.
62 *> \endverbatim
63 *>
64 *> \param[in] UPLO
65 *> \verbatim
66 *>          UPLO is CHARACTER*1
67 *>          = 'U':  Upper triangle of A is stored;
68 *>          = 'L':  Lower triangle of A is stored.
69 *> \endverbatim
70 *>
71 *> \param[in] N
72 *> \verbatim
73 *>          N is INTEGER
74 *>          The order of the matrix A.  N >= 0.
75 *> \endverbatim
76 *>
77 *> \param[in,out] A
78 *> \verbatim
79 *>          A is REAL array, dimension (LDA, N)
80 *>          On entry, the symmetric matrix A.  If UPLO = 'U', the
81 *>          leading N-by-N upper triangular part of A contains the
82 *>          upper triangular part of the matrix A.  If UPLO = 'L',
83 *>          the leading N-by-N lower triangular part of A contains
84 *>          the lower triangular part of the matrix A.
85 *>          On exit, if JOBZ = 'V', then if INFO = 0, A contains the
86 *>          orthonormal eigenvectors of the matrix A.
87 *>          If JOBZ = 'N', then on exit the lower triangle (if UPLO='L')
88 *>          or the upper triangle (if UPLO='U') of A, including the
89 *>          diagonal, is destroyed.
90 *> \endverbatim
91 *>
92 *> \param[in] LDA
93 *> \verbatim
94 *>          LDA is INTEGER
95 *>          The leading dimension of the array A.  LDA >= max(1,N).
96 *> \endverbatim
97 *>
98 *> \param[out] W
99 *> \verbatim
100 *>          W is REAL array, dimension (N)
101 *>          If INFO = 0, the eigenvalues in ascending order.
102 *> \endverbatim
103 *>
104 *> \param[out] WORK
105 *> \verbatim
106 *>          WORK is REAL array,
107 *>                                         dimension (LWORK)
108 *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
109 *> \endverbatim
110 *>
111 *> \param[in] LWORK
112 *> \verbatim
113 *>          LWORK is INTEGER
114 *>          The dimension of the array WORK.
115 *>          If N <= 1,               LWORK must be at least 1.
116 *>          If JOBZ = 'N' and N > 1, LWORK must be at least 2*N+1.
117 *>          If JOBZ = 'V' and N > 1, LWORK must be at least 
118 *>                                                1 + 6*N + 2*N**2.
119 *>
120 *>          If LWORK = -1, then a workspace query is assumed; the routine
121 *>          only calculates the optimal sizes of the WORK and IWORK
122 *>          arrays, returns these values as the first entries of the WORK
123 *>          and IWORK arrays, and no error message related to LWORK or
124 *>          LIWORK is issued by XERBLA.
125 *> \endverbatim
126 *>
127 *> \param[out] IWORK
128 *> \verbatim
129 *>          IWORK is INTEGER array, dimension (MAX(1,LIWORK))
130 *>          On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
131 *> \endverbatim
132 *>
133 *> \param[in] LIWORK
134 *> \verbatim
135 *>          LIWORK is INTEGER
136 *>          The dimension of the array IWORK.
137 *>          If N <= 1,                LIWORK must be at least 1.
138 *>          If JOBZ  = 'N' and N > 1, LIWORK must be at least 1.
139 *>          If JOBZ  = 'V' and N > 1, LIWORK must be at least 3 + 5*N.
140 *>
141 *>          If LIWORK = -1, then a workspace query is assumed; the
142 *>          routine only calculates the optimal sizes of the WORK and
143 *>          IWORK arrays, returns these values as the first entries of
144 *>          the WORK and IWORK arrays, and no error message related to
145 *>          LWORK or LIWORK is issued by XERBLA.
146 *> \endverbatim
147 *>
148 *> \param[out] INFO
149 *> \verbatim
150 *>          INFO is INTEGER
151 *>          = 0:  successful exit
152 *>          < 0:  if INFO = -i, the i-th argument had an illegal value
153 *>          > 0:  if INFO = i and JOBZ = 'N', then the algorithm failed
154 *>                to converge; i off-diagonal elements of an intermediate
155 *>                tridiagonal form did not converge to zero;
156 *>                if INFO = i and JOBZ = 'V', then the algorithm failed
157 *>                to compute an eigenvalue while working on the submatrix
158 *>                lying in rows and columns INFO/(N+1) through
159 *>                mod(INFO,N+1).
160 *> \endverbatim
161 *
162 *  Authors:
163 *  ========
164 *
165 *> \author Univ. of Tennessee 
166 *> \author Univ. of California Berkeley 
167 *> \author Univ. of Colorado Denver 
168 *> \author NAG Ltd. 
169 *
170 *> \date November 2011
171 *
172 *> \ingroup realSYeigen
173 *
174 *> \par Contributors:
175 *  ==================
176 *>
177 *> Jeff Rutter, Computer Science Division, University of California
178 *> at Berkeley, USA \n
179 *>  Modified by Francoise Tisseur, University of Tennessee \n
180 *>  Modified description of INFO. Sven, 16 Feb 05. \n
181 *>
182 *  =====================================================================
183       SUBROUTINE SSYEVD( JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, IWORK,
184      $                   LIWORK, INFO )
185 *
186 *  -- LAPACK driver routine (version 3.4.0) --
187 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
188 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
189 *     November 2011
190 *
191 *     .. Scalar Arguments ..
192       CHARACTER          JOBZ, UPLO
193       INTEGER            INFO, LDA, LIWORK, LWORK, N
194 *     ..
195 *     .. Array Arguments ..
196       INTEGER            IWORK( * )
197       REAL               A( LDA, * ), W( * ), WORK( * )
198 *     ..
199 *
200 *  =====================================================================
201 *
202 *     .. Parameters ..
203       REAL               ZERO, ONE
204       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
205 *     ..
206 *     .. Local Scalars ..
207 *
208       LOGICAL            LOWER, LQUERY, WANTZ
209       INTEGER            IINFO, INDE, INDTAU, INDWK2, INDWRK, ISCALE,
210      $                   LIOPT, LIWMIN, LLWORK, LLWRK2, LOPT, LWMIN
211       REAL               ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA,
212      $                   SMLNUM
213 *     ..
214 *     .. External Functions ..
215       LOGICAL            LSAME
216       INTEGER            ILAENV
217       REAL               SLAMCH, SLANSY
218       EXTERNAL           ILAENV, LSAME, SLAMCH, SLANSY
219 *     ..
220 *     .. External Subroutines ..
221       EXTERNAL           SLACPY, SLASCL, SORMTR, SSCAL, SSTEDC, SSTERF,
222      $                   SSYTRD, XERBLA
223 *     ..
224 *     .. Intrinsic Functions ..
225       INTRINSIC          MAX, SQRT
226 *     ..
227 *     .. Executable Statements ..
228 *
229 *     Test the input parameters.
230 *
231       WANTZ = LSAME( JOBZ, 'V' )
232       LOWER = LSAME( UPLO, 'L' )
233       LQUERY = ( LWORK.EQ.-1 .OR. LIWORK.EQ.-1 )
234 *
235       INFO = 0
236       IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
237          INFO = -1
238       ELSE IF( .NOT.( LOWER .OR. LSAME( UPLO, 'U' ) ) ) THEN
239          INFO = -2
240       ELSE IF( N.LT.0 ) THEN
241          INFO = -3
242       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
243          INFO = -5
244       END IF
245 *
246       IF( INFO.EQ.0 ) THEN
247          IF( N.LE.1 ) THEN
248             LIWMIN = 1
249             LWMIN = 1
250             LOPT = LWMIN
251             LIOPT = LIWMIN
252          ELSE
253             IF( WANTZ ) THEN
254                LIWMIN = 3 + 5*N
255                LWMIN = 1 + 6*N + 2*N**2
256             ELSE
257                LIWMIN = 1
258                LWMIN = 2*N + 1
259             END IF
260             LOPT = MAX( LWMIN, 2*N +
261      $                  ILAENV( 1, 'SSYTRD', UPLO, N, -1, -1, -1 ) )
262             LIOPT = LIWMIN
263          END IF
264          WORK( 1 ) = LOPT
265          IWORK( 1 ) = LIOPT
266 *
267          IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
268             INFO = -8
269          ELSE IF( LIWORK.LT.LIWMIN .AND. .NOT.LQUERY ) THEN
270             INFO = -10
271          END IF
272       END IF
273 *
274       IF( INFO.NE.0 ) THEN
275          CALL XERBLA( 'SSYEVD', -INFO )
276          RETURN
277       ELSE IF( LQUERY ) THEN
278          RETURN 
279       END IF
280 *
281 *     Quick return if possible
282 *
283       IF( N.EQ.0 )
284      $   RETURN
285 *
286       IF( N.EQ.1 ) THEN
287          W( 1 ) = A( 1, 1 )
288          IF( WANTZ )
289      $      A( 1, 1 ) = ONE
290          RETURN 
291       END IF
292 *
293 *     Get machine constants.
294 *
295       SAFMIN = SLAMCH( 'Safe minimum' )
296       EPS = SLAMCH( 'Precision' )
297       SMLNUM = SAFMIN / EPS
298       BIGNUM = ONE / SMLNUM
299       RMIN = SQRT( SMLNUM )
300       RMAX = SQRT( BIGNUM )
301 *
302 *     Scale matrix to allowable range, if necessary.
303 *
304       ANRM = SLANSY( 'M', UPLO, N, A, LDA, WORK )
305       ISCALE = 0
306       IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
307          ISCALE = 1
308          SIGMA = RMIN / ANRM
309       ELSE IF( ANRM.GT.RMAX ) THEN
310          ISCALE = 1
311          SIGMA = RMAX / ANRM
312       END IF
313       IF( ISCALE.EQ.1 )
314      $   CALL SLASCL( UPLO, 0, 0, ONE, SIGMA, N, N, A, LDA, INFO )
315 *
316 *     Call SSYTRD to reduce symmetric matrix to tridiagonal form.
317 *
318       INDE = 1
319       INDTAU = INDE + N
320       INDWRK = INDTAU + N
321       LLWORK = LWORK - INDWRK + 1
322       INDWK2 = INDWRK + N*N
323       LLWRK2 = LWORK - INDWK2 + 1
324 *
325       CALL SSYTRD( UPLO, N, A, LDA, W, WORK( INDE ), WORK( INDTAU ),
326      $             WORK( INDWRK ), LLWORK, IINFO )
327 *
328 *     For eigenvalues only, call SSTERF.  For eigenvectors, first call
329 *     SSTEDC to generate the eigenvector matrix, WORK(INDWRK), of the
330 *     tridiagonal matrix, then call SORMTR to multiply it by the
331 *     Householder transformations stored in A.
332 *
333       IF( .NOT.WANTZ ) THEN
334          CALL SSTERF( N, W, WORK( INDE ), INFO )
335       ELSE
336          CALL SSTEDC( 'I', N, W, WORK( INDE ), WORK( INDWRK ), N,
337      $                WORK( INDWK2 ), LLWRK2, IWORK, LIWORK, INFO )
338          CALL SORMTR( 'L', UPLO, 'N', N, N, A, LDA, WORK( INDTAU ),
339      $                WORK( INDWRK ), N, WORK( INDWK2 ), LLWRK2, IINFO )
340          CALL SLACPY( 'A', N, N, WORK( INDWRK ), N, A, LDA )
341       END IF
342 *
343 *     If matrix was scaled, then rescale eigenvalues appropriately.
344 *
345       IF( ISCALE.EQ.1 )
346      $   CALL SSCAL( N, ONE / SIGMA, W, 1 )
347 *
348       WORK( 1 ) = LOPT
349       IWORK( 1 ) = LIOPT
350 *
351       RETURN
352 *
353 *     End of SSYEVD
354 *
355       END