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