141 SUBROUTINE ctbcon( NORM, UPLO, DIAG, N, KD, AB, LDAB, RCOND, WORK,
149 CHARACTER DIAG, NORM, UPLO
150 INTEGER INFO, KD, LDAB, N
155 COMPLEX AB( LDAB, * ), WORK( * )
162 parameter( one = 1.0e+0, zero = 0.0e+0 )
165 LOGICAL NOUNIT, ONENRM, UPPER
167 INTEGER IX, KASE, KASE1
168 REAL AINVNM, ANORM, SCALE, SMLNUM, XNORM
178 EXTERNAL lsame, icamax, clantb, slamch
184 INTRINSIC abs, aimag, max, real
190 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
197 upper = lsame( uplo,
'U' )
198 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
199 nounit = lsame( diag,
'N' )
201 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
203 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
205 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag,
'U' ) )
THEN
207 ELSE IF( n.LT.0 )
THEN
209 ELSE IF( kd.LT.0 )
THEN
211 ELSE IF( ldab.LT.kd+1 )
THEN
215 CALL xerbla(
'CTBCON', -info )
227 smlnum = slamch(
'Safe minimum' )*real( max( n, 1 ) )
231 anorm = clantb( norm, uplo, diag, n, kd, ab, ldab, rwork )
235 IF( anorm.GT.zero )
THEN
248 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
250 IF( kase.EQ.kase1 )
THEN
254 CALL clatbs( uplo,
'No transpose', diag, normin, n, kd,
255 $ ab, ldab, work, scale, rwork, info )
260 CALL clatbs( uplo,
'Conjugate transpose', diag, normin,
261 $ n, kd, ab, ldab, work, scale, rwork, info )
267 IF( scale.NE.one )
THEN
268 ix = icamax( n, work, 1 )
269 xnorm = cabs1( work( ix ) )
270 IF( scale.LT.xnorm*smlnum .OR. scale.EQ.zero )
272 CALL csrscl( n, scale, work, 1 )
280 $ rcond = ( one / anorm ) / ainvnm
subroutine xerbla(srname, info)
subroutine clacn2(n, v, x, est, kase, isave)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine clatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)
CLATBS solves a triangular banded system of equations.
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.
subroutine ctbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, rwork, info)
CTBCON