3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DPTCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dptcon.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dptcon.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dptcon.f">
21 * SUBROUTINE DPTCON( N, D, E, ANORM, RCOND, WORK, INFO )
23 * .. Scalar Arguments ..
25 * DOUBLE PRECISION ANORM, RCOND
27 * .. Array Arguments ..
28 * DOUBLE PRECISION D( * ), E( * ), WORK( * )
37 *> DPTCON computes the reciprocal of the condition number (in the
38 *> 1-norm) of a real symmetric positive definite tridiagonal matrix
39 *> using the factorization A = L*D*L**T or A = U**T*D*U computed by
42 *> Norm(inv(A)) is computed by a direct method, and the reciprocal of
43 *> the condition number is computed as
44 *> RCOND = 1 / (ANORM * norm(inv(A))).
53 *> The order of the matrix A. N >= 0.
58 *> D is DOUBLE PRECISION array, dimension (N)
59 *> The n diagonal elements of the diagonal matrix D from the
60 *> factorization of A, as computed by DPTTRF.
65 *> E is DOUBLE PRECISION array, dimension (N-1)
66 *> The (n-1) off-diagonal elements of the unit bidiagonal factor
67 *> U or L from the factorization of A, as computed by DPTTRF.
72 *> ANORM is DOUBLE PRECISION
73 *> The 1-norm of the original matrix A.
78 *> RCOND is DOUBLE PRECISION
79 *> The reciprocal of the condition number of the matrix A,
80 *> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is the
81 *> 1-norm of inv(A) computed in this routine.
86 *> WORK is DOUBLE PRECISION array, dimension (N)
92 *> = 0: successful exit
93 *> < 0: if INFO = -i, the i-th argument had an illegal value
99 *> \author Univ. of Tennessee
100 *> \author Univ. of California Berkeley
101 *> \author Univ. of Colorado Denver
104 *> \date September 2012
106 *> \ingroup doublePTcomputational
108 *> \par Further Details:
109 * =====================
113 *> The method used is described in Nicholas J. Higham, "Efficient
114 *> Algorithms for Computing the Condition Number of a Tridiagonal
115 *> Matrix", SIAM J. Sci. Stat. Comput., Vol. 7, No. 1, January 1986.
118 * =====================================================================
119 SUBROUTINE DPTCON( N, D, E, ANORM, RCOND, WORK, INFO )
121 * -- LAPACK computational routine (version 3.4.2) --
122 * -- LAPACK is a software package provided by Univ. of Tennessee, --
123 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126 * .. Scalar Arguments ..
128 DOUBLE PRECISION ANORM, RCOND
130 * .. Array Arguments ..
131 DOUBLE PRECISION D( * ), E( * ), WORK( * )
134 * =====================================================================
137 DOUBLE PRECISION ONE, ZERO
138 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
140 * .. Local Scalars ..
142 DOUBLE PRECISION AINVNM
144 * .. External Functions ..
148 * .. External Subroutines ..
151 * .. Intrinsic Functions ..
154 * .. Executable Statements ..
156 * Test the input arguments.
161 ELSE IF( ANORM.LT.ZERO ) THEN
165 CALL XERBLA( 'DPTCON', -INFO )
169 * Quick return if possible
175 ELSE IF( ANORM.EQ.ZERO ) THEN
179 * Check that D(1:N) is positive.
186 * Solve M(A) * x = e, where M(A) = (m(i,j)) is given by
188 * m(i,j) = abs(A(i,j)), i = j,
189 * m(i,j) = -abs(A(i,j)), i .ne. j,
191 * and e = [ 1, 1, ..., 1 ]**T. Note M(A) = M(L)*D*M(L)**T.
193 * Solve M(L) * x = e.
197 WORK( I ) = ONE + WORK( I-1 )*ABS( E( I-1 ) )
200 * Solve D * M(L)**T * x = b.
202 WORK( N ) = WORK( N ) / D( N )
203 DO 30 I = N - 1, 1, -1
204 WORK( I ) = WORK( I ) / D( I ) + WORK( I+1 )*ABS( E( I ) )
207 * Compute AINVNM = max(x(i)), 1<=i<=n.
209 IX = IDAMAX( N, WORK, 1 )
210 AINVNM = ABS( WORK( IX ) )
212 * Compute the reciprocal condition number.
215 $ RCOND = ( ONE / AINVNM ) / ANORM