130 SUBROUTINE sgecon( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
144 REAL A( LDA, * ), WORK( * )
151 parameter( one = 1.0e+0, zero = 0.0e+0 )
156 INTEGER IX, KASE, KASE1
157 REAL AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
163 LOGICAL LSAME, SISNAN
166 EXTERNAL lsame, isamax, slamch, sisnan
176 hugeval = slamch(
'Overflow' )
181 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
182 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
184 ELSE IF( n.LT.0 )
THEN
186 ELSE IF( lda.LT.max( 1, n ) )
THEN
188 ELSE IF( anorm.LT.zero )
THEN
192 CALL xerbla(
'SGECON', -info )
202 ELSE IF( anorm.EQ.zero )
THEN
204 ELSE IF( sisnan( anorm ) )
THEN
208 ELSE IF( anorm.GT.hugeval )
THEN
213 smlnum = slamch(
'Safe minimum' )
226 CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
228 IF( kase.EQ.kase1 )
THEN
232 CALL slatrs(
'Lower',
'No transpose',
'Unit', normin, n, a,
233 $ lda, work, sl, work( 2*n+1 ), info )
237 CALL slatrs(
'Upper',
'No transpose',
'Non-unit', normin, n,
238 $ a, lda, work, su, work( 3*n+1 ), info )
243 CALL slatrs(
'Upper',
'Transpose',
'Non-unit', normin, n, a,
244 $ lda, work, su, work( 3*n+1 ), info )
248 CALL slatrs(
'Lower',
'Transpose',
'Unit', normin, n, a,
249 $ lda, work, sl, work( 2*n+1 ), info )
256 IF( scale.NE.one )
THEN
257 ix = isamax( n, work, 1 )
258 IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
260 CALL srscl( n, scale, work, 1 )
267 IF( ainvnm.NE.zero )
THEN
268 rcond = ( one / ainvnm ) / anorm
276 IF( sisnan( rcond ) .OR. rcond.GT.hugeval )
subroutine xerbla(srname, info)
subroutine sgecon(norm, n, a, lda, anorm, rcond, work, iwork, info)
SGECON
subroutine slacn2(n, v, x, isgn, est, kase, isave)
SLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine slatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
SLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
subroutine srscl(n, sa, sx, incx)
SRSCL multiplies a vector by the reciprocal of a real scalar.