119 SUBROUTINE dpocon( UPLO, N, A, LDA, ANORM, RCOND, WORK, IWORK,
129 DOUBLE PRECISION ANORM, RCOND
133 DOUBLE PRECISION A( LDA, * ), WORK( * )
139 DOUBLE PRECISION ONE, ZERO
140 parameter( one = 1.0d+0, zero = 0.0d+0 )
146 DOUBLE PRECISION AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
154 DOUBLE PRECISION DLAMCH
155 EXTERNAL lsame, idamax, dlamch
168 upper = lsame( uplo,
'U' )
169 IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
171 ELSE IF( n.LT.0 )
THEN
173 ELSE IF( lda.LT.
max( 1, n ) )
THEN
175 ELSE IF( anorm.LT.zero )
THEN
179 CALL xerbla(
'DPOCON', -info )
189 ELSE IF( anorm.EQ.zero )
THEN
193 smlnum = dlamch(
'Safe minimum' )
200 CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
206 CALL dlatrs(
'Upper',
'Transpose',
'Non-unit', normin, n, a,
207 $ lda, work, scalel, work( 2*n+1 ), info )
212 CALL dlatrs(
'Upper',
'No transpose',
'Non-unit', normin, n,
213 $ a, lda, work, scaleu, work( 2*n+1 ), info )
218 CALL dlatrs(
'Lower', 'no transpose
', 'non-unit
', NORMIN, N,
219 $ A, LDA, WORK, SCALEL, WORK( 2*N+1 ), INFO )
224 CALL DLATRS( 'lower
', 'transpose
', 'non-unit
', NORMIN, N, A,
225 $ LDA, WORK, SCALEU, WORK( 2*N+1 ), INFO )
230 SCALE = SCALEL*SCALEU
231.NE.
IF( SCALEONE ) THEN
232 IX = IDAMAX( N, WORK, 1 )
233.LT..OR..EQ.
IF( SCALEABS( WORK( IX ) )*SMLNUM SCALEZERO )
235 CALL DRSCL( N, SCALE, WORK, 1 )
243 $ RCOND = ( ONE / AINVNM ) / ANORM
subroutine xerbla(srname, info)
XERBLA
subroutine drscl(n, sa, sx, incx)
DRSCL multiplies a vector by the reciprocal of a real scalar.
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.
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...
subroutine dpocon(uplo, n, a, lda, anorm, rcond, work, iwork, info)
DPOCON