LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zpteqr.f
Go to the documentation of this file.
1*> \brief \b ZPTEQR
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZPTEQR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zpteqr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zpteqr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpteqr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZPTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER COMPZ
23* INTEGER INFO, LDZ, N
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION D( * ), E( * ), WORK( * )
27* COMPLEX*16 Z( LDZ, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZPTEQR computes all eigenvalues and, optionally, eigenvectors of a
37*> symmetric positive definite tridiagonal matrix by first factoring the
38*> matrix using DPTTRF and then calling ZBDSQR to compute the singular
39*> values of the bidiagonal factor.
40*>
41*> This routine computes the eigenvalues of the positive definite
42*> tridiagonal matrix to high relative accuracy. This means that if the
43*> eigenvalues range over many orders of magnitude in size, then the
44*> small eigenvalues and corresponding eigenvectors will be computed
45*> more accurately than, for example, with the standard QR method.
46*>
47*> The eigenvectors of a full or band positive definite Hermitian matrix
48*> can also be found if ZHETRD, ZHPTRD, or ZHBTRD has been used to
49*> reduce this matrix to tridiagonal form. (The reduction to
50*> tridiagonal form, however, may preclude the possibility of obtaining
51*> high relative accuracy in the small eigenvalues of the original
52*> matrix, if these eigenvalues range over many orders of magnitude.)
53*> \endverbatim
54*
55* Arguments:
56* ==========
57*
58*> \param[in] COMPZ
59*> \verbatim
60*> COMPZ is CHARACTER*1
61*> = 'N': Compute eigenvalues only.
62*> = 'V': Compute eigenvectors of original Hermitian
63*> matrix also. Array Z contains the unitary matrix
64*> used to reduce the original matrix to tridiagonal
65*> form.
66*> = 'I': Compute eigenvectors of tridiagonal matrix also.
67*> \endverbatim
68*>
69*> \param[in] N
70*> \verbatim
71*> N is INTEGER
72*> The order of the matrix. N >= 0.
73*> \endverbatim
74*>
75*> \param[in,out] D
76*> \verbatim
77*> D is DOUBLE PRECISION array, dimension (N)
78*> On entry, the n diagonal elements of the tridiagonal matrix.
79*> On normal exit, D contains the eigenvalues, in descending
80*> order.
81*> \endverbatim
82*>
83*> \param[in,out] E
84*> \verbatim
85*> E is DOUBLE PRECISION array, dimension (N-1)
86*> On entry, the (n-1) subdiagonal elements of the tridiagonal
87*> matrix.
88*> On exit, E has been destroyed.
89*> \endverbatim
90*>
91*> \param[in,out] Z
92*> \verbatim
93*> Z is COMPLEX*16 array, dimension (LDZ, N)
94*> On entry, if COMPZ = 'V', the unitary matrix used in the
95*> reduction to tridiagonal form.
96*> On exit, if COMPZ = 'V', the orthonormal eigenvectors of the
97*> original Hermitian matrix;
98*> if COMPZ = 'I', the orthonormal eigenvectors of the
99*> tridiagonal matrix.
100*> If INFO > 0 on exit, Z contains the eigenvectors associated
101*> with only the stored eigenvalues.
102*> If COMPZ = 'N', then Z is not referenced.
103*> \endverbatim
104*>
105*> \param[in] LDZ
106*> \verbatim
107*> LDZ is INTEGER
108*> The leading dimension of the array Z. LDZ >= 1, and if
109*> COMPZ = 'V' or 'I', LDZ >= max(1,N).
110*> \endverbatim
111*>
112*> \param[out] WORK
113*> \verbatim
114*> WORK is DOUBLE PRECISION array, dimension (4*N)
115*> \endverbatim
116*>
117*> \param[out] INFO
118*> \verbatim
119*> INFO is INTEGER
120*> = 0: successful exit.
121*> < 0: if INFO = -i, the i-th argument had an illegal value.
122*> > 0: if INFO = i, and i is:
123*> <= N the Cholesky factorization of the matrix could
124*> not be performed because the leading principal
125*> minor of order i was not positive.
126*> > N the SVD algorithm failed to converge;
127*> if INFO = N+i, i off-diagonal elements of the
128*> bidiagonal factor did not converge to zero.
129*> \endverbatim
130*
131* Authors:
132* ========
133*
134*> \author Univ. of Tennessee
135*> \author Univ. of California Berkeley
136*> \author Univ. of Colorado Denver
137*> \author NAG Ltd.
138*
139*> \ingroup pteqr
140*
141* =====================================================================
142 SUBROUTINE zpteqr( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
143*
144* -- LAPACK computational routine --
145* -- LAPACK is a software package provided by Univ. of Tennessee, --
146* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
147*
148* .. Scalar Arguments ..
149 CHARACTER COMPZ
150 INTEGER INFO, LDZ, N
151* ..
152* .. Array Arguments ..
153 DOUBLE PRECISION D( * ), E( * ), WORK( * )
154 COMPLEX*16 Z( LDZ, * )
155* ..
156*
157* ====================================================================
158*
159* .. Parameters ..
160 COMPLEX*16 CZERO, CONE
161 parameter( czero = ( 0.0d+0, 0.0d+0 ),
162 $ cone = ( 1.0d+0, 0.0d+0 ) )
163* ..
164* .. External Functions ..
165 LOGICAL LSAME
166 EXTERNAL lsame
167* ..
168* .. External Subroutines ..
169 EXTERNAL dpttrf, xerbla, zbdsqr, zlaset
170* ..
171* .. Local Arrays ..
172 COMPLEX*16 C( 1, 1 ), VT( 1, 1 )
173* ..
174* .. Local Scalars ..
175 INTEGER I, ICOMPZ, NRU
176* ..
177* .. Intrinsic Functions ..
178 INTRINSIC max, sqrt
179* ..
180* .. Executable Statements ..
181*
182* Test the input parameters.
183*
184 info = 0
185*
186 IF( lsame( compz, 'N' ) ) THEN
187 icompz = 0
188 ELSE IF( lsame( compz, 'V' ) ) THEN
189 icompz = 1
190 ELSE IF( lsame( compz, 'I' ) ) THEN
191 icompz = 2
192 ELSE
193 icompz = -1
194 END IF
195 IF( icompz.LT.0 ) THEN
196 info = -1
197 ELSE IF( n.LT.0 ) THEN
198 info = -2
199 ELSE IF( ( ldz.LT.1 ) .OR. ( icompz.GT.0 .AND. ldz.LT.max( 1,
200 $ n ) ) ) THEN
201 info = -6
202 END IF
203 IF( info.NE.0 ) THEN
204 CALL xerbla( 'ZPTEQR', -info )
205 RETURN
206 END IF
207*
208* Quick return if possible
209*
210 IF( n.EQ.0 )
211 $ RETURN
212*
213 IF( n.EQ.1 ) THEN
214 IF( icompz.GT.0 )
215 $ z( 1, 1 ) = cone
216 RETURN
217 END IF
218 IF( icompz.EQ.2 )
219 $ CALL zlaset( 'Full', n, n, czero, cone, z, ldz )
220*
221* Call DPTTRF to factor the matrix.
222*
223 CALL dpttrf( n, d, e, info )
224 IF( info.NE.0 )
225 $ RETURN
226 DO 10 i = 1, n
227 d( i ) = sqrt( d( i ) )
228 10 CONTINUE
229 DO 20 i = 1, n - 1
230 e( i ) = e( i )*d( i )
231 20 CONTINUE
232*
233* Call ZBDSQR to compute the singular values/vectors of the
234* bidiagonal factor.
235*
236 IF( icompz.GT.0 ) THEN
237 nru = n
238 ELSE
239 nru = 0
240 END IF
241 CALL zbdsqr( 'Lower', n, 0, nru, 0, d, e, vt, 1, z, ldz, c, 1,
242 $ work, info )
243*
244* Square the singular values.
245*
246 IF( info.EQ.0 ) THEN
247 DO 30 i = 1, n
248 d( i ) = d( i )*d( i )
249 30 CONTINUE
250 ELSE
251 info = n + info
252 END IF
253*
254 RETURN
255*
256* End of ZPTEQR
257*
258 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zbdsqr(uplo, n, ncvt, nru, ncc, d, e, vt, ldvt, u, ldu, c, ldc, rwork, info)
ZBDSQR
Definition zbdsqr.f:233
subroutine zlaset(uplo, m, n, alpha, beta, a, lda)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition zlaset.f:104
subroutine zpteqr(compz, n, d, e, z, ldz, work, info)
ZPTEQR
Definition zpteqr.f:143
subroutine dpttrf(n, d, e, info)
DPTTRF
Definition dpttrf.f:89