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