3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SPTEQR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spteqr.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spteqr.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spteqr.f">
21 * SUBROUTINE SPTEQR( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDZ, N
27 * .. Array Arguments ..
28 * REAL D( * ), E( * ), WORK( * ), Z( LDZ, * )
37 *> SPTEQR computes all eigenvalues and, optionally, eigenvectors of a
38 *> symmetric positive definite tridiagonal matrix by first factoring the
39 *> matrix using SPTTRF, and then calling SBDSQR to compute the singular
40 *> values of the bidiagonal factor.
42 *> This routine computes the eigenvalues of the positive definite
43 *> tridiagonal matrix to high relative accuracy. This means that if the
44 *> eigenvalues range over many orders of magnitude in size, then the
45 *> small eigenvalues and corresponding eigenvectors will be computed
46 *> more accurately than, for example, with the standard QR method.
48 *> The eigenvectors of a full or band symmetric positive definite matrix
49 *> can also be found if SSYTRD, SSPTRD, or SSBTRD has been used to
50 *> reduce this matrix to tridiagonal form. (The reduction to tridiagonal
51 *> form, however, may preclude the possibility of obtaining high
52 *> relative accuracy in the small eigenvalues of the original matrix, if
53 *> these eigenvalues range over many orders of magnitude.)
61 *> COMPZ is CHARACTER*1
62 *> = 'N': Compute eigenvalues only.
63 *> = 'V': Compute eigenvectors of original symmetric
64 *> matrix also. Array Z contains the orthogonal
65 *> matrix used to reduce the original matrix to
67 *> = 'I': Compute eigenvectors of tridiagonal matrix also.
73 *> The order of the matrix. N >= 0.
78 *> D is REAL array, dimension (N)
79 *> On entry, the n diagonal elements of the tridiagonal
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 REAL array, dimension (LDZ, N)
96 *> On entry, if COMPZ = 'V', the orthogonal matrix used in the
97 *> reduction to tridiagonal form.
98 *> On exit, if COMPZ = 'V', the orthonormal eigenvectors of the
99 *> original symmetric 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 realPTcomputational
145 * =====================================================================
146 SUBROUTINE SPTEQR( 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( * ), Z( LDZ, * )
161 * =====================================================================
165 PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0 )
167 * .. External Functions ..
171 * .. External Subroutines ..
172 EXTERNAL SBDSQR, SLASET, SPTTRF, XERBLA
175 REAL C( 1, 1 ), VT( 1, 1 )
177 * .. Local Scalars ..
178 INTEGER I, ICOMPZ, NRU
180 * .. Intrinsic Functions ..
183 * .. Executable Statements ..
185 * Test the input parameters.
189 IF( LSAME( COMPZ, 'N' ) ) THEN
191 ELSE IF( LSAME( COMPZ, 'V' ) ) THEN
193 ELSE IF( LSAME( COMPZ, 'I' ) ) THEN
198 IF( ICOMPZ.LT.0 ) THEN
200 ELSE IF( N.LT.0 ) THEN
202 ELSE IF( ( LDZ.LT.1 ) .OR. ( ICOMPZ.GT.0 .AND. LDZ.LT.MAX( 1,
207 CALL XERBLA( 'SPTEQR', -INFO )
211 * Quick return if possible
222 $ CALL SLASET( 'Full', N, N, ZERO, ONE, Z, LDZ )
224 * Call SPTTRF to factor the matrix.
226 CALL SPTTRF( N, D, E, INFO )
230 D( I ) = SQRT( D( I ) )
233 E( I ) = E( I )*D( I )
236 * Call SBDSQR to compute the singular values/vectors of the
239 IF( ICOMPZ.GT.0 ) THEN
244 CALL SBDSQR( 'Lower', N, 0, NRU, 0, D, E, VT, 1, Z, LDZ, C, 1,
247 * Square the singular values.
251 D( I ) = D( I )*D( I )