183 SUBROUTINE dgerfs( TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB,
184 $ X, LDX, FERR, BERR, WORK, IWORK, INFO )
192 INTEGER INFO, LDA, LDAF, LDB, LDX, N, NRHS
195 INTEGER IPIV( * ), IWORK( * )
196 DOUBLE PRECISION A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
197 $ berr( * ), ferr( * ), work( * ), x( ldx, * )
204 parameter( itmax = 5 )
205 DOUBLE PRECISION ZERO
206 parameter( zero = 0.0d+0 )
208 parameter( one = 1.0d+0 )
210 parameter( two = 2.0d+0 )
211 DOUBLE PRECISION THREE
212 parameter( three = 3.0d+0 )
217 INTEGER COUNT, I, J, K, KASE, NZ
218 DOUBLE PRECISION EPS, LSTRES, S, SAFE1, SAFE2, SAFMIN, XK
231 DOUBLE PRECISION DLAMCH
232 EXTERNAL lsame, dlamch
239 notran = lsame( trans,
'N' )
240 IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
241 $ lsame( trans,
'C' ) )
THEN
243 ELSE IF( n.LT.0 )
THEN
245 ELSE IF( nrhs.LT.0 )
THEN
247 ELSE IF( lda.LT.max( 1, n ) )
THEN
249 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
251 ELSE IF( ldb.LT.max( 1, n ) )
THEN
253 ELSE IF( ldx.LT.max( 1, n ) )
THEN
257 CALL xerbla(
'DGERFS', -info )
263 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
280 eps = dlamch(
'Epsilon' )
281 safmin = dlamch(
'Safe minimum' )
298 CALL dcopy( n, b( 1, j ), 1, work( n+1 ), 1 )
299 CALL dgemv( trans, n, n, -one, a, lda, x( 1, j ), 1, one,
312 work( i ) = abs( b( i, j ) )
319 xk = abs( x( k, j ) )
321 work( i ) = work( i ) + abs( a( i, k ) )*xk
328 s = s + abs( a( i, k ) )*abs( x( i, j ) )
330 work( k ) = work( k ) + s
335 IF( work( i ).GT.safe2 )
THEN
336 s = max( s, abs( work( n+i ) ) / work( i ) )
338 s = max( s, ( abs( work( n+i ) )+safe1 ) /
339 $ ( work( i )+safe1 ) )
350 IF( berr( j ).GT.eps .AND. two*berr( j ).LE.lstres .AND.
351 $ count.LE.itmax )
THEN
355 CALL dgetrs( trans, n, 1, af, ldaf, ipiv, work( n+1 ), n,
357 CALL daxpy( n, one, work( n+1 ), 1, x( 1, j ), 1 )
386 IF( work( i ).GT.safe2 )
THEN
387 work( i ) = abs( work( n+i ) ) + nz*eps*work( i )
389 work( i ) = abs( work( n+i ) ) + nz*eps*work( i ) + safe1
395 CALL dlacn2( n, work( 2*n+1 ), work( n+1 ), iwork, ferr( j ),
402 CALL dgetrs( transt, n, 1, af, ldaf, ipiv, work( n+1 ),
405 work( n+i ) = work( i )*work( n+i )
412 work( n+i ) = work( i )*work( n+i )
414 CALL dgetrs( trans, n, 1, af, ldaf, ipiv, work( n+1 ), n,
424 lstres = max( lstres, abs( x( i, j ) ) )
427 $ ferr( j ) = ferr( j ) / lstres
subroutine xerbla(srname, info)
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
subroutine dgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DGERFS
subroutine dgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
DGETRS
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...