LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zspcon()

subroutine zspcon ( character uplo,
integer n,
complex*16, dimension( * ) ap,
integer, dimension( * ) ipiv,
double precision anorm,
double precision rcond,
complex*16, dimension( * ) work,
integer info )

ZSPCON

Download ZSPCON + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZSPCON estimates the reciprocal of the condition number (in the
!> 1-norm) of a complex symmetric packed matrix A using the
!> factorization A = U*D*U**T or A = L*D*L**T computed by ZSPTRF.
!>
!> An estimate is obtained for norm(inv(A)), and the reciprocal of the
!> condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          Specifies whether the details of the factorization are stored
!>          as an upper or lower triangular matrix.
!>          = 'U':  Upper triangular, form is A = U*D*U**T;
!>          = 'L':  Lower triangular, form is A = L*D*L**T.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]AP
!>          AP is COMPLEX*16 array, dimension (N*(N+1)/2)
!>          The block diagonal matrix D and the multipliers used to
!>          obtain the factor U or L as computed by ZSPTRF, stored as a
!>          packed triangular matrix.
!> 
[in]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>          Details of the interchanges and the block structure of D
!>          as determined by ZSPTRF.
!> 
[in]ANORM
!>          ANORM is DOUBLE PRECISION
!>          The 1-norm of the original matrix A.
!> 
[out]RCOND
!>          RCOND is DOUBLE PRECISION
!>          The reciprocal of the condition number of the matrix A,
!>          computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
!>          estimate of the 1-norm of inv(A) computed in this routine.
!> 
[out]WORK
!>          WORK is COMPLEX*16 array, dimension (2*N)
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 115 of file zspcon.f.

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*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
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
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: