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

◆ dgecon()

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

DGECON

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

Purpose:
 DGECON estimates the reciprocal of the condition number of a general
 real matrix A, in either the 1-norm or the infinity-norm, using
 the LU factorization computed by DGETRF.

 An estimate is obtained for norm(inv(A)), and the reciprocal of the
 condition number is computed as
    RCOND = 1 / ( norm(A) * norm(inv(A)) ).
Parameters
[in]NORM
          NORM is CHARACTER*1
          Specifies whether the 1-norm condition number or the
          infinity-norm condition number is required:
          = '1' or 'O':  1-norm;
          = 'I':         Infinity-norm.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          The factors L and U from the factorization A = P*L*U
          as computed by DGETRF.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]ANORM
          ANORM is DOUBLE PRECISION
          If NORM = '1' or 'O', the 1-norm of the original matrix A.
          If NORM = 'I', the infinity-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/(norm(A) * norm(inv(A))).
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (4*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.
                NaNs are illegal values for ANORM, and they propagate to
                the output parameter RCOND.
                Infinity is illegal for ANORM, and it propagates to the output
                parameter RCOND as 0.
          = 1:  if RCOND = NaN, or
                   RCOND = Inf, or
                   the computed norm of the inverse of A is 0.
                In the latter, RCOND = 0 is returned.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 130 of file dgecon.f.

132*
133* -- LAPACK computational routine --
134* -- LAPACK is a software package provided by Univ. of Tennessee, --
135* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136*
137* .. Scalar Arguments ..
138 CHARACTER NORM
139 INTEGER INFO, LDA, N
140 DOUBLE PRECISION ANORM, RCOND
141* ..
142* .. Array Arguments ..
143 INTEGER IWORK( * )
144 DOUBLE PRECISION A( LDA, * ), WORK( * )
145* ..
146*
147* =====================================================================
148*
149* .. Parameters ..
150 DOUBLE PRECISION ONE, ZERO
151 parameter( one = 1.0d+0, zero = 0.0d+0 )
152* ..
153* .. Local Scalars ..
154 LOGICAL ONENRM
155 CHARACTER NORMIN
156 INTEGER IX, KASE, KASE1
157 DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
158* ..
159* .. Local Arrays ..
160 INTEGER ISAVE( 3 )
161* ..
162* .. External Functions ..
163 LOGICAL LSAME, DISNAN
164 INTEGER IDAMAX
165 DOUBLE PRECISION DLAMCH
166 EXTERNAL lsame, idamax, dlamch, disnan
167* ..
168* .. External Subroutines ..
169 EXTERNAL dlacn2, dlatrs, drscl, xerbla
170* ..
171* .. Intrinsic Functions ..
172 INTRINSIC abs, max
173* ..
174* .. Executable Statements ..
175*
176 hugeval = dlamch( 'Overflow' )
177*
178* Test the input parameters.
179*
180 info = 0
181 onenrm = norm.EQ.'1' .OR. lsame( norm, 'O' )
182 IF( .NOT.onenrm .AND. .NOT.lsame( norm, 'I' ) ) THEN
183 info = -1
184 ELSE IF( n.LT.0 ) THEN
185 info = -2
186 ELSE IF( lda.LT.max( 1, n ) ) THEN
187 info = -4
188 ELSE IF( anorm.LT.zero ) THEN
189 info = -5
190 END IF
191 IF( info.NE.0 ) THEN
192 CALL xerbla( 'DGECON', -info )
193 RETURN
194 END IF
195*
196* Quick return if possible
197*
198 rcond = zero
199 IF( n.EQ.0 ) THEN
200 rcond = one
201 RETURN
202 ELSE IF( anorm.EQ.zero ) THEN
203 RETURN
204 ELSE IF( disnan( anorm ) ) THEN
205 rcond = anorm
206 info = -5
207 RETURN
208 ELSE IF( anorm.GT.hugeval ) THEN
209 info = -5
210 RETURN
211 END IF
212*
213 smlnum = dlamch( 'Safe minimum' )
214*
215* Estimate the norm of inv(A).
216*
217 ainvnm = zero
218 normin = 'N'
219 IF( onenrm ) THEN
220 kase1 = 1
221 ELSE
222 kase1 = 2
223 END IF
224 kase = 0
225 10 CONTINUE
226 CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
227 IF( kase.NE.0 ) THEN
228 IF( kase.EQ.kase1 ) THEN
229*
230* Multiply by inv(L).
231*
232 CALL dlatrs( 'Lower', 'No transpose', 'Unit', normin, n, a,
233 $ lda, work, sl, work( 2*n+1 ), info )
234*
235* Multiply by inv(U).
236*
237 CALL dlatrs( 'Upper', 'No transpose', 'Non-unit', normin, n,
238 $ a, lda, work, su, work( 3*n+1 ), info )
239 ELSE
240*
241* Multiply by inv(U**T).
242*
243 CALL dlatrs( 'Upper', 'Transpose', 'Non-unit', normin, n, a,
244 $ lda, work, su, work( 3*n+1 ), info )
245*
246* Multiply by inv(L**T).
247*
248 CALL dlatrs( 'Lower', 'Transpose', 'Unit', normin, n, a,
249 $ lda, work, sl, work( 2*n+1 ), info )
250 END IF
251*
252* Divide X by 1/(SL*SU) if doing so will not cause overflow.
253*
254 scale = sl*su
255 normin = 'Y'
256 IF( scale.NE.one ) THEN
257 ix = idamax( n, work, 1 )
258 IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
259 $ GO TO 20
260 CALL drscl( n, scale, work, 1 )
261 END IF
262 GO TO 10
263 END IF
264*
265* Compute the estimate of the reciprocal condition number.
266*
267 IF( ainvnm.NE.zero ) THEN
268 rcond = ( one / ainvnm ) / anorm
269 ELSE
270 info = 1
271 RETURN
272 END IF
273*
274* Check for NaNs and Infs
275*
276 IF( disnan( rcond ) .OR. rcond.GT.hugeval )
277 $ info = 1
278*
279 20 CONTINUE
280 RETURN
281*
282* End of DGECON
283*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function idamax(n, dx, incx)
IDAMAX
Definition idamax.f:71
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
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
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:238
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:84
Here is the call graph for this function:
Here is the caller graph for this function: