LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dstev.f
Go to the documentation of this file.
1 *> \brief <b> DSTEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER 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 DSTEV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dstev.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dstev.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dstev.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DSTEV( JOBZ, N, D, E, Z, LDZ, WORK, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER JOBZ
25 * INTEGER INFO, LDZ, N
26 * ..
27 * .. Array Arguments ..
28 * DOUBLE PRECISION D( * ), E( * ), WORK( * ), Z( LDZ, * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> DSTEV computes all eigenvalues and, optionally, eigenvectors of a
38 *> real symmetric tridiagonal 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] N
52 *> \verbatim
53 *> N is INTEGER
54 *> The order of the matrix. N >= 0.
55 *> \endverbatim
56 *>
57 *> \param[in,out] D
58 *> \verbatim
59 *> D is DOUBLE PRECISION array, dimension (N)
60 *> On entry, the n diagonal elements of the tridiagonal matrix
61 *> A.
62 *> On exit, if INFO = 0, the eigenvalues in ascending order.
63 *> \endverbatim
64 *>
65 *> \param[in,out] E
66 *> \verbatim
67 *> E is DOUBLE PRECISION array, dimension (N-1)
68 *> On entry, the (n-1) subdiagonal elements of the tridiagonal
69 *> matrix A, stored in elements 1 to N-1 of E.
70 *> On exit, the contents of E are destroyed.
71 *> \endverbatim
72 *>
73 *> \param[out] Z
74 *> \verbatim
75 *> Z is DOUBLE PRECISION array, dimension (LDZ, N)
76 *> If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal
77 *> eigenvectors of the matrix A, with the i-th column of Z
78 *> holding the eigenvector associated with D(i).
79 *> If JOBZ = 'N', then Z is not referenced.
80 *> \endverbatim
81 *>
82 *> \param[in] LDZ
83 *> \verbatim
84 *> LDZ is INTEGER
85 *> The leading dimension of the array Z. LDZ >= 1, and if
86 *> JOBZ = 'V', LDZ >= max(1,N).
87 *> \endverbatim
88 *>
89 *> \param[out] WORK
90 *> \verbatim
91 *> WORK is DOUBLE PRECISION array, dimension (max(1,2*N-2))
92 *> If JOBZ = 'N', WORK is not referenced.
93 *> \endverbatim
94 *>
95 *> \param[out] INFO
96 *> \verbatim
97 *> INFO is INTEGER
98 *> = 0: successful exit
99 *> < 0: if INFO = -i, the i-th argument had an illegal value
100 *> > 0: if INFO = i, the algorithm failed to converge; i
101 *> off-diagonal elements of E did not converge to zero.
102 *> \endverbatim
103 *
104 * Authors:
105 * ========
106 *
107 *> \author Univ. of Tennessee
108 *> \author Univ. of California Berkeley
109 *> \author Univ. of Colorado Denver
110 *> \author NAG Ltd.
111 *
112 *> \date November 2011
113 *
114 *> \ingroup doubleOTHEReigen
115 *
116 * =====================================================================
117  SUBROUTINE dstev( JOBZ, N, D, E, Z, LDZ, WORK, INFO )
118 *
119 * -- LAPACK driver routine (version 3.4.0) --
120 * -- LAPACK is a software package provided by Univ. of Tennessee, --
121 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
122 * November 2011
123 *
124 * .. Scalar Arguments ..
125  CHARACTER jobz
126  INTEGER info, ldz, n
127 * ..
128 * .. Array Arguments ..
129  DOUBLE PRECISION d( * ), e( * ), work( * ), z( ldz, * )
130 * ..
131 *
132 * =====================================================================
133 *
134 * .. Parameters ..
135  DOUBLE PRECISION zero, one
136  parameter( zero = 0.0d0, one = 1.0d0 )
137 * ..
138 * .. Local Scalars ..
139  LOGICAL wantz
140  INTEGER imax, iscale
141  DOUBLE PRECISION bignum, eps, rmax, rmin, safmin, sigma, smlnum,
142  $ tnrm
143 * ..
144 * .. External Functions ..
145  LOGICAL lsame
146  DOUBLE PRECISION dlamch, dlanst
147  EXTERNAL lsame, dlamch, dlanst
148 * ..
149 * .. External Subroutines ..
150  EXTERNAL dscal, dsteqr, dsterf, xerbla
151 * ..
152 * .. Intrinsic Functions ..
153  INTRINSIC sqrt
154 * ..
155 * .. Executable Statements ..
156 *
157 * Test the input parameters.
158 *
159  wantz = lsame( jobz, 'V' )
160 *
161  info = 0
162  IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
163  info = -1
164  ELSE IF( n.LT.0 ) THEN
165  info = -2
166  ELSE IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
167  info = -6
168  END IF
169 *
170  IF( info.NE.0 ) THEN
171  CALL xerbla( 'DSTEV ', -info )
172  return
173  END IF
174 *
175 * Quick return if possible
176 *
177  IF( n.EQ.0 )
178  $ return
179 *
180  IF( n.EQ.1 ) THEN
181  IF( wantz )
182  $ z( 1, 1 ) = one
183  return
184  END IF
185 *
186 * Get machine constants.
187 *
188  safmin = dlamch( 'Safe minimum' )
189  eps = dlamch( 'Precision' )
190  smlnum = safmin / eps
191  bignum = one / smlnum
192  rmin = sqrt( smlnum )
193  rmax = sqrt( bignum )
194 *
195 * Scale matrix to allowable range, if necessary.
196 *
197  iscale = 0
198  tnrm = dlanst( 'M', n, d, e )
199  IF( tnrm.GT.zero .AND. tnrm.LT.rmin ) THEN
200  iscale = 1
201  sigma = rmin / tnrm
202  ELSE IF( tnrm.GT.rmax ) THEN
203  iscale = 1
204  sigma = rmax / tnrm
205  END IF
206  IF( iscale.EQ.1 ) THEN
207  CALL dscal( n, sigma, d, 1 )
208  CALL dscal( n-1, sigma, e( 1 ), 1 )
209  END IF
210 *
211 * For eigenvalues only, call DSTERF. For eigenvalues and
212 * eigenvectors, call DSTEQR.
213 *
214  IF( .NOT.wantz ) THEN
215  CALL dsterf( n, d, e, info )
216  ELSE
217  CALL dsteqr( 'I', n, d, e, z, ldz, work, info )
218  END IF
219 *
220 * If matrix was scaled, then rescale eigenvalues appropriately.
221 *
222  IF( iscale.EQ.1 ) THEN
223  IF( info.EQ.0 ) THEN
224  imax = n
225  ELSE
226  imax = info - 1
227  END IF
228  CALL dscal( imax, one / sigma, d, 1 )
229  END IF
230 *
231  return
232 *
233 * End of DSTEV
234 *
235  END