117 SUBROUTINE cppcon( UPLO, N, AP, ANORM, RCOND, WORK, RWORK, INFO )
130 COMPLEX AP( * ), WORK( * )
137 parameter( one = 1.0e+0, zero = 0.0e+0 )
143 REAL AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
153 EXTERNAL lsame, icamax, slamch
159 INTRINSIC abs, aimag, real
165 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
172 upper = lsame( uplo,
'U' )
173 IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
175 ELSE IF( n.LT.0 )
THEN
177 ELSE IF( anorm.LT.zero )
THEN
181 CALL xerbla(
'CPPCON', -info )
191 ELSE IF( anorm.EQ.zero )
THEN
195 smlnum = slamch(
'Safe minimum' )
202 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
208 CALL clatps(
'Upper',
'Conjugate transpose',
'Non-unit',
209 $ normin, n, ap, work, scalel, rwork, info )
214 CALL clatps(
'Upper',
'No transpose',
'Non-unit', normin, n,
215 $ ap, work, scaleu, rwork, info )
220 CALL clatps(
'Lower',
'No transpose',
'Non-unit', normin, n,
221 $ ap, work, scalel, rwork, info )
226 CALL clatps(
'Lower',
'Conjugate transpose',
'Non-unit',
227 $ normin, n, ap, work, scaleu, rwork, info )
232 scale = scalel*scaleu
233 IF( scale.NE.one )
THEN
234 ix = icamax( n, work, 1 )
235 IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
237 CALL csrscl( n, scale, work, 1 )
245 $ rcond = ( one / ainvnm ) / anorm
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 clatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)
CLATPS solves a triangular system of equations with the matrix held in packed storage.
subroutine cppcon(uplo, n, ap, anorm, rcond, work, rwork, info)
CPPCON
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.