3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CPTEQR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cpteqr.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cpteqr.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cpteqr.f">
21 * SUBROUTINE CPTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDZ, N
27 * .. Array Arguments ..
28 * REAL D( * ), E( * ), WORK( * )
38 *> CPTEQR computes all eigenvalues and, optionally, eigenvectors of a
39 *> symmetric positive definite tridiagonal matrix by first factoring the
40 *> matrix using SPTTRF and then calling CBDSQR to compute the singular
41 *> values of the bidiagonal factor.
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.
49 *> The eigenvectors of a full or band positive definite Hermitian matrix
50 *> can also be found if CHETRD, CHPTRD, or CHBTRD 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.)
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
68 *> = 'I': Compute eigenvectors of tridiagonal matrix also.
74 *> The order of the matrix. N >= 0.
79 *> D is REAL array, dimension (N)
80 *> On entry, the n diagonal elements of the tridiagonal matrix.
81 *> On normal exit, D contains the eigenvalues, in descending
87 *> E is REAL array, dimension (N-1)
88 *> On entry, the (n-1) subdiagonal elements of the tridiagonal
90 *> On exit, E has been destroyed.
95 *> Z is COMPLEX 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.
110 *> The leading dimension of the array Z. LDZ >= 1, and if
111 *> COMPZ = 'V' or 'I', LDZ >= max(1,N).
116 *> WORK is REAL array, dimension (4*N)
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 i-th principal minor
127 *> was not positive definite.
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.
136 *> \author Univ. of Tennessee
137 *> \author Univ. of California Berkeley
138 *> \author Univ. of Colorado Denver
141 *> \date September 2012
143 *> \ingroup complexPTcomputational
145 * =====================================================================
146 SUBROUTINE CPTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
148 * -- LAPACK computational routine (version 3.4.2) --
149 * -- LAPACK is a software package provided by Univ. of Tennessee, --
150 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153 * .. Scalar Arguments ..
157 * .. Array Arguments ..
158 REAL D( * ), E( * ), WORK( * )
162 * ====================================================================
166 PARAMETER ( CZERO = ( 0.0E+0, 0.0E+0 ),
167 $ CONE = ( 1.0E+0, 0.0E+0 ) )
169 * .. External Functions ..
173 * .. External Subroutines ..
174 EXTERNAL CBDSQR, CLASET, SPTTRF, XERBLA
177 COMPLEX C( 1, 1 ), VT( 1, 1 )
179 * .. Local Scalars ..
180 INTEGER I, ICOMPZ, NRU
182 * .. Intrinsic Functions ..
185 * .. Executable Statements ..
187 * Test the input parameters.
191 IF( LSAME( COMPZ, 'N' ) ) THEN
193 ELSE IF( LSAME( COMPZ, 'V' ) ) THEN
195 ELSE IF( LSAME( COMPZ, 'I' ) ) THEN
200 IF( ICOMPZ.LT.0 ) THEN
202 ELSE IF( N.LT.0 ) THEN
204 ELSE IF( ( LDZ.LT.1 ) .OR. ( ICOMPZ.GT.0 .AND. LDZ.LT.MAX( 1,
209 CALL XERBLA( 'CPTEQR', -INFO )
213 * Quick return if possible
224 $ CALL CLASET( 'Full', N, N, CZERO, CONE, Z, LDZ )
226 * Call SPTTRF to factor the matrix.
228 CALL SPTTRF( N, D, E, INFO )
232 D( I ) = SQRT( D( I ) )
235 E( I ) = E( I )*D( I )
238 * Call CBDSQR to compute the singular values/vectors of the
241 IF( ICOMPZ.GT.0 ) THEN
246 CALL CBDSQR( 'Lower', N, 0, NRU, 0, D, E, VT, 1, Z, LDZ, C, 1,
249 * Square the singular values.
253 D( I ) = D( I )*D( I )