LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zspcon.f
Go to the documentation of this file.
1*> \brief \b ZSPCON
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZSPCON + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zspcon.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zspcon.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspcon.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZSPCON( UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, N
24* DOUBLE PRECISION ANORM, RCOND
25* ..
26* .. Array Arguments ..
27* INTEGER IPIV( * )
28* COMPLEX*16 AP( * ), WORK( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZSPCON estimates the reciprocal of the condition number (in the
38*> 1-norm) of a complex symmetric packed matrix A using the
39*> factorization A = U*D*U**T or A = L*D*L**T computed by ZSPTRF.
40*>
41*> An estimate is obtained for norm(inv(A)), and the reciprocal of the
42*> condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
43*> \endverbatim
44*
45* Arguments:
46* ==========
47*
48*> \param[in] UPLO
49*> \verbatim
50*> UPLO is CHARACTER*1
51*> Specifies whether the details of the factorization are stored
52*> as an upper or lower triangular matrix.
53*> = 'U': Upper triangular, form is A = U*D*U**T;
54*> = 'L': Lower triangular, form is A = L*D*L**T.
55*> \endverbatim
56*>
57*> \param[in] N
58*> \verbatim
59*> N is INTEGER
60*> The order of the matrix A. N >= 0.
61*> \endverbatim
62*>
63*> \param[in] AP
64*> \verbatim
65*> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
66*> The block diagonal matrix D and the multipliers used to
67*> obtain the factor U or L as computed by ZSPTRF, stored as a
68*> packed triangular matrix.
69*> \endverbatim
70*>
71*> \param[in] IPIV
72*> \verbatim
73*> IPIV is INTEGER array, dimension (N)
74*> Details of the interchanges and the block structure of D
75*> as determined by ZSPTRF.
76*> \endverbatim
77*>
78*> \param[in] ANORM
79*> \verbatim
80*> ANORM is DOUBLE PRECISION
81*> The 1-norm of the original matrix A.
82*> \endverbatim
83*>
84*> \param[out] RCOND
85*> \verbatim
86*> RCOND is DOUBLE PRECISION
87*> The reciprocal of the condition number of the matrix A,
88*> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
89*> estimate of the 1-norm of inv(A) computed in this routine.
90*> \endverbatim
91*>
92*> \param[out] WORK
93*> \verbatim
94*> WORK is COMPLEX*16 array, dimension (2*N)
95*> \endverbatim
96*>
97*> \param[out] INFO
98*> \verbatim
99*> INFO is INTEGER
100*> = 0: successful exit
101*> < 0: if INFO = -i, the i-th argument had an illegal value
102*> \endverbatim
103*
104* Authors:
105* ========
106*
107*> \author Univ. of Tennessee
108*> \author Univ. of California Berkeley
109*> \author Univ. of Colorado Denver
110*> \author NAG Ltd.
111*
112*> \ingroup hpcon
113*
114* =====================================================================
115 SUBROUTINE zspcon( UPLO, N, AP, IPIV, ANORM, RCOND, WORK,
116 $ 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 CHARACTER UPLO
124 INTEGER INFO, N
125 DOUBLE PRECISION ANORM, RCOND
126* ..
127* .. Array Arguments ..
128 INTEGER IPIV( * )
129 COMPLEX*16 AP( * ), WORK( * )
130* ..
131*
132* =====================================================================
133*
134* .. Parameters ..
135 DOUBLE PRECISION ONE, ZERO
136 parameter( one = 1.0d+0, zero = 0.0d+0 )
137* ..
138* .. Local Scalars ..
139 LOGICAL UPPER
140 INTEGER I, IP, KASE
141 DOUBLE PRECISION AINVNM
142* ..
143* .. Local Arrays ..
144 INTEGER ISAVE( 3 )
145* ..
146* .. External Functions ..
147 LOGICAL LSAME
148 EXTERNAL lsame
149* ..
150* .. External Subroutines ..
151 EXTERNAL xerbla, zlacn2, zsptrs
152* ..
153* .. Executable Statements ..
154*
155* Test the input parameters.
156*
157 info = 0
158 upper = lsame( uplo, 'U' )
159 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
160 info = -1
161 ELSE IF( n.LT.0 ) THEN
162 info = -2
163 ELSE IF( anorm.LT.zero ) THEN
164 info = -5
165 END IF
166 IF( info.NE.0 ) THEN
167 CALL xerbla( 'ZSPCON', -info )
168 RETURN
169 END IF
170*
171* Quick return if possible
172*
173 rcond = zero
174 IF( n.EQ.0 ) THEN
175 rcond = one
176 RETURN
177 ELSE IF( anorm.LE.zero ) THEN
178 RETURN
179 END IF
180*
181* Check that the diagonal matrix D is nonsingular.
182*
183 IF( upper ) THEN
184*
185* Upper triangular storage: examine D from bottom to top
186*
187 ip = n*( n+1 ) / 2
188 DO 10 i = n, 1, -1
189 IF( ipiv( i ).GT.0 .AND. ap( ip ).EQ.zero )
190 $ RETURN
191 ip = ip - i
192 10 CONTINUE
193 ELSE
194*
195* Lower triangular storage: examine D from top to bottom.
196*
197 ip = 1
198 DO 20 i = 1, n
199 IF( ipiv( i ).GT.0 .AND. ap( ip ).EQ.zero )
200 $ RETURN
201 ip = ip + n - i + 1
202 20 CONTINUE
203 END IF
204*
205* Estimate the 1-norm of the inverse.
206*
207 kase = 0
208 30 CONTINUE
209 CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
210 IF( kase.NE.0 ) THEN
211*
212* Multiply by inv(L*D*L**T) or inv(U*D*U**T).
213*
214 CALL zsptrs( uplo, n, 1, ap, ipiv, work, n, info )
215 GO TO 30
216 END IF
217*
218* Compute the estimate of the reciprocal condition number.
219*
220 IF( ainvnm.NE.zero )
221 $ rcond = ( one / ainvnm ) / anorm
222*
223 RETURN
224*
225* End of ZSPCON
226*
227 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zspcon(uplo, n, ap, ipiv, anorm, rcond, work, info)
ZSPCON
Definition zspcon.f:117
subroutine zsptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)
ZSPTRS
Definition zsptrs.f:113
subroutine zlacn2(n, v, x, est, kase, isave)
ZLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition zlacn2.f:131