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

◆ dpocon()

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

DPOCON

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

Purpose:
!>
!> DPOCON estimates the reciprocal of the condition number (in the
!> 1-norm) of a real symmetric positive definite matrix using the
!> Cholesky factorization A = U**T*U or A = L*L**T computed by DPOTRF.
!>
!> 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
!>          = 'U':  Upper triangle of A is stored;
!>          = 'L':  Lower triangle of A is stored.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]A
!>          A is DOUBLE PRECISION array, dimension (LDA,N)
!>          The triangular factor U or L from the Cholesky factorization
!>          A = U**T*U or A = L*L**T, as computed by DPOTRF.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in]ANORM
!>          ANORM is DOUBLE PRECISION
!>          The 1-norm (or infinity-norm) of the symmetric 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 (3*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 117 of file dpocon.f.

119*
120* -- LAPACK computational routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 CHARACTER UPLO
126 INTEGER INFO, LDA, N
127 DOUBLE PRECISION ANORM, RCOND
128* ..
129* .. Array Arguments ..
130 INTEGER IWORK( * )
131 DOUBLE PRECISION A( LDA, * ), WORK( * )
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 DOUBLE PRECISION ONE, ZERO
138 parameter( one = 1.0d+0, zero = 0.0d+0 )
139* ..
140* .. Local Scalars ..
141 LOGICAL UPPER
142 CHARACTER NORMIN
143 INTEGER IX, KASE
144 DOUBLE PRECISION AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
145* ..
146* .. Local Arrays ..
147 INTEGER ISAVE( 3 )
148* ..
149* .. External Functions ..
150 LOGICAL LSAME
151 INTEGER IDAMAX
152 DOUBLE PRECISION DLAMCH
153 EXTERNAL lsame, idamax, dlamch
154* ..
155* .. External Subroutines ..
156 EXTERNAL dlacn2, dlatrs, drscl, xerbla
157* ..
158* .. Intrinsic Functions ..
159 INTRINSIC abs, max
160* ..
161* .. Executable Statements ..
162*
163* Test the input parameters.
164*
165 info = 0
166 upper = lsame( uplo, 'U' )
167 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
168 info = -1
169 ELSE IF( n.LT.0 ) THEN
170 info = -2
171 ELSE IF( lda.LT.max( 1, n ) ) THEN
172 info = -4
173 ELSE IF( anorm.LT.zero ) THEN
174 info = -5
175 END IF
176 IF( info.NE.0 ) THEN
177 CALL xerbla( 'DPOCON', -info )
178 RETURN
179 END IF
180*
181* Quick return if possible
182*
183 rcond = zero
184 IF( n.EQ.0 ) THEN
185 rcond = one
186 RETURN
187 ELSE IF( anorm.EQ.zero ) THEN
188 RETURN
189 END IF
190*
191 smlnum = dlamch( 'Safe minimum' )
192*
193* Estimate the 1-norm of inv(A).
194*
195 kase = 0
196 normin = 'N'
197 10 CONTINUE
198 CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
199 IF( kase.NE.0 ) THEN
200 IF( upper ) THEN
201*
202* Multiply by inv(U**T).
203*
204 CALL dlatrs( 'Upper', 'Transpose', 'Non-unit', normin, n,
205 $ a,
206 $ lda, work, scalel, work( 2*n+1 ), info )
207 normin = 'Y'
208*
209* Multiply by inv(U).
210*
211 CALL dlatrs( 'Upper', 'No transpose', 'Non-unit', normin,
212 $ n,
213 $ a, lda, work, scaleu, work( 2*n+1 ), info )
214 ELSE
215*
216* Multiply by inv(L).
217*
218 CALL dlatrs( 'Lower', 'No transpose', 'Non-unit', normin,
219 $ n,
220 $ a, lda, work, scalel, work( 2*n+1 ), info )
221 normin = 'Y'
222*
223* Multiply by inv(L**T).
224*
225 CALL dlatrs( 'Lower', 'Transpose', 'Non-unit', normin, n,
226 $ a,
227 $ lda, work, scaleu, work( 2*n+1 ), info )
228 END IF
229*
230* Multiply by 1/SCALE if doing so will not cause overflow.
231*
232 scale = scalel*scaleu
233 IF( scale.NE.one ) THEN
234 ix = idamax( n, work, 1 )
235 IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
236 $ GO TO 20
237 CALL drscl( n, scale, work, 1 )
238 END IF
239 GO TO 10
240 END IF
241*
242* Compute the estimate of the reciprocal condition number.
243*
244 IF( ainvnm.NE.zero )
245 $ rcond = ( one / ainvnm ) / anorm
246*
247 20 CONTINUE
248 RETURN
249*
250* End of DPOCON
251*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function idamax(n, dx, incx)
IDAMAX
Definition idamax.f:71
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:134
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
subroutine dlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
DLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition dlatrs.f:237
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine drscl(n, sa, sx, incx)
DRSCL multiplies a vector by the reciprocal of a real scalar.
Definition drscl.f:82
Here is the call graph for this function:
Here is the caller graph for this function: