LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dptcon.f
Go to the documentation of this file.
1*> \brief \b DPTCON
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DPTCON + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dptcon.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dptcon.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dptcon.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DPTCON( N, D, E, ANORM, RCOND, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, N
23* DOUBLE PRECISION ANORM, RCOND
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION D( * ), E( * ), WORK( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> DPTCON computes the reciprocal of the condition number (in the
36*> 1-norm) of a real symmetric positive definite tridiagonal matrix
37*> using the factorization A = L*D*L**T or A = U**T*D*U computed by
38*> DPTTRF.
39*>
40*> Norm(inv(A)) is computed by a direct method, and the reciprocal of
41*> the condition number is computed as
42*> RCOND = 1 / (ANORM * norm(inv(A))).
43*> \endverbatim
44*
45* Arguments:
46* ==========
47*
48*> \param[in] N
49*> \verbatim
50*> N is INTEGER
51*> The order of the matrix A. N >= 0.
52*> \endverbatim
53*>
54*> \param[in] D
55*> \verbatim
56*> D is DOUBLE PRECISION array, dimension (N)
57*> The n diagonal elements of the diagonal matrix D from the
58*> factorization of A, as computed by DPTTRF.
59*> \endverbatim
60*>
61*> \param[in] E
62*> \verbatim
63*> E is DOUBLE PRECISION array, dimension (N-1)
64*> The (n-1) off-diagonal elements of the unit bidiagonal factor
65*> U or L from the factorization of A, as computed by DPTTRF.
66*> \endverbatim
67*>
68*> \param[in] ANORM
69*> \verbatim
70*> ANORM is DOUBLE PRECISION
71*> The 1-norm of the original matrix A.
72*> \endverbatim
73*>
74*> \param[out] RCOND
75*> \verbatim
76*> RCOND is DOUBLE PRECISION
77*> The reciprocal of the condition number of the matrix A,
78*> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is the
79*> 1-norm of inv(A) computed in this routine.
80*> \endverbatim
81*>
82*> \param[out] WORK
83*> \verbatim
84*> WORK is DOUBLE PRECISION array, dimension (N)
85*> \endverbatim
86*>
87*> \param[out] INFO
88*> \verbatim
89*> INFO is INTEGER
90*> = 0: successful exit
91*> < 0: if INFO = -i, the i-th argument had an illegal value
92*> \endverbatim
93*
94* Authors:
95* ========
96*
97*> \author Univ. of Tennessee
98*> \author Univ. of California Berkeley
99*> \author Univ. of Colorado Denver
100*> \author NAG Ltd.
101*
102*> \ingroup ptcon
103*
104*> \par Further Details:
105* =====================
106*>
107*> \verbatim
108*>
109*> The method used is described in Nicholas J. Higham, "Efficient
110*> Algorithms for Computing the Condition Number of a Tridiagonal
111*> Matrix", SIAM J. Sci. Stat. Comput., Vol. 7, No. 1, January 1986.
112*> \endverbatim
113*>
114* =====================================================================
115 SUBROUTINE dptcon( N, D, E, ANORM, RCOND, WORK, INFO )
116*
117* -- LAPACK computational routine --
118* -- LAPACK is a software package provided by Univ. of Tennessee, --
119* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120*
121* .. Scalar Arguments ..
122 INTEGER INFO, N
123 DOUBLE PRECISION ANORM, RCOND
124* ..
125* .. Array Arguments ..
126 DOUBLE PRECISION D( * ), E( * ), WORK( * )
127* ..
128*
129* =====================================================================
130*
131* .. Parameters ..
132 DOUBLE PRECISION ONE, ZERO
133 parameter( one = 1.0d+0, zero = 0.0d+0 )
134* ..
135* .. Local Scalars ..
136 INTEGER I, IX
137 DOUBLE PRECISION AINVNM
138* ..
139* .. External Functions ..
140 INTEGER IDAMAX
141 EXTERNAL idamax
142* ..
143* .. External Subroutines ..
144 EXTERNAL xerbla
145* ..
146* .. Intrinsic Functions ..
147 INTRINSIC abs
148* ..
149* .. Executable Statements ..
150*
151* Test the input arguments.
152*
153 info = 0
154 IF( n.LT.0 ) THEN
155 info = -1
156 ELSE IF( anorm.LT.zero ) THEN
157 info = -4
158 END IF
159 IF( info.NE.0 ) THEN
160 CALL xerbla( 'DPTCON', -info )
161 RETURN
162 END IF
163*
164* Quick return if possible
165*
166 rcond = zero
167 IF( n.EQ.0 ) THEN
168 rcond = one
169 RETURN
170 ELSE IF( anorm.EQ.zero ) THEN
171 RETURN
172 END IF
173*
174* Check that D(1:N) is positive.
175*
176 DO 10 i = 1, n
177 IF( d( i ).LE.zero )
178 $ RETURN
179 10 CONTINUE
180*
181* Solve M(A) * x = e, where M(A) = (m(i,j)) is given by
182*
183* m(i,j) = abs(A(i,j)), i = j,
184* m(i,j) = -abs(A(i,j)), i .ne. j,
185*
186* and e = [ 1, 1, ..., 1 ]**T. Note M(A) = M(L)*D*M(L)**T.
187*
188* Solve M(L) * x = e.
189*
190 work( 1 ) = one
191 DO 20 i = 2, n
192 work( i ) = one + work( i-1 )*abs( e( i-1 ) )
193 20 CONTINUE
194*
195* Solve D * M(L)**T * x = b.
196*
197 work( n ) = work( n ) / d( n )
198 DO 30 i = n - 1, 1, -1
199 work( i ) = work( i ) / d( i ) + work( i+1 )*abs( e( i ) )
200 30 CONTINUE
201*
202* Compute AINVNM = max(x(i)), 1<=i<=n.
203*
204 ix = idamax( n, work, 1 )
205 ainvnm = abs( work( ix ) )
206*
207* Compute the reciprocal condition number.
208*
209 IF( ainvnm.NE.zero )
210 $ rcond = ( one / ainvnm ) / anorm
211*
212 RETURN
213*
214* End of DPTCON
215*
216 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dptcon(n, d, e, anorm, rcond, work, info)
DPTCON
Definition dptcon.f:116