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

◆ dsycon()

subroutine dsycon ( character  uplo,
integer  n,
double precision, dimension( lda, * )  a,
integer  lda,
integer, dimension( * )  ipiv,
double precision  anorm,
double precision  rcond,
double precision, dimension( * )  work,
integer, dimension( * )  iwork,
integer  info 
)

DSYCON

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

Purpose:
 DSYCON estimates the reciprocal of the condition number (in the
 1-norm) of a real symmetric matrix A using the factorization
 A = U*D*U**T or A = L*D*L**T computed by DSYTRF.

 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]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by DSYTRF.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          Details of the interchanges and the block structure of D
          as determined by DSYTRF.
[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 DOUBLE PRECISION array, dimension (2*N)
[out]IWORK
          IWORK is INTEGER array, dimension (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 128 of file dsycon.f.

130*
131* -- LAPACK computational routine --
132* -- LAPACK is a software package provided by Univ. of Tennessee, --
133* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
134*
135* .. Scalar Arguments ..
136 CHARACTER UPLO
137 INTEGER INFO, LDA, N
138 DOUBLE PRECISION ANORM, RCOND
139* ..
140* .. Array Arguments ..
141 INTEGER IPIV( * ), IWORK( * )
142 DOUBLE PRECISION A( LDA, * ), WORK( * )
143* ..
144*
145* =====================================================================
146*
147* .. Parameters ..
148 DOUBLE PRECISION ONE, ZERO
149 parameter( one = 1.0d+0, zero = 0.0d+0 )
150* ..
151* .. Local Scalars ..
152 LOGICAL UPPER
153 INTEGER I, KASE
154 DOUBLE PRECISION AINVNM
155* ..
156* .. Local Arrays ..
157 INTEGER ISAVE( 3 )
158* ..
159* .. External Functions ..
160 LOGICAL LSAME
161 EXTERNAL lsame
162* ..
163* .. External Subroutines ..
164 EXTERNAL dlacn2, dsytrs, xerbla
165* ..
166* .. Intrinsic Functions ..
167 INTRINSIC max
168* ..
169* .. Executable Statements ..
170*
171* Test the input parameters.
172*
173 info = 0
174 upper = lsame( uplo, 'U' )
175 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
176 info = -1
177 ELSE IF( n.LT.0 ) THEN
178 info = -2
179 ELSE IF( lda.LT.max( 1, n ) ) THEN
180 info = -4
181 ELSE IF( anorm.LT.zero ) THEN
182 info = -6
183 END IF
184 IF( info.NE.0 ) THEN
185 CALL xerbla( 'DSYCON', -info )
186 RETURN
187 END IF
188*
189* Quick return if possible
190*
191 rcond = zero
192 IF( n.EQ.0 ) THEN
193 rcond = one
194 RETURN
195 ELSE IF( anorm.LE.zero ) THEN
196 RETURN
197 END IF
198*
199* Check that the diagonal matrix D is nonsingular.
200*
201 IF( upper ) THEN
202*
203* Upper triangular storage: examine D from bottom to top
204*
205 DO 10 i = n, 1, -1
206 IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
207 $ RETURN
208 10 CONTINUE
209 ELSE
210*
211* Lower triangular storage: examine D from top to bottom.
212*
213 DO 20 i = 1, n
214 IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
215 $ RETURN
216 20 CONTINUE
217 END IF
218*
219* Estimate the 1-norm of the inverse.
220*
221 kase = 0
222 30 CONTINUE
223 CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
224 IF( kase.NE.0 ) THEN
225*
226* Multiply by inv(L*D*L**T) or inv(U*D*U**T).
227*
228 CALL dsytrs( uplo, n, 1, a, lda, ipiv, work, n, info )
229 GO TO 30
230 END IF
231*
232* Compute the estimate of the reciprocal condition number.
233*
234 IF( ainvnm.NE.zero )
235 $ rcond = ( one / ainvnm ) / anorm
236*
237 RETURN
238*
239* End of DSYCON
240*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dsytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
DSYTRS
Definition dsytrs.f:120
subroutine dlacn2(n, v, x, isgn, est, kase, isave)
DLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition dlacn2.f:136
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: