346 SUBROUTINE dgesvx( FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV,
347 $ EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR,
348 $ WORK, IWORK, INFO )
355 CHARACTER EQUED, FACT, TRANS
356 INTEGER INFO, LDA, LDAF, LDB, LDX, N, NRHS
357 DOUBLE PRECISION RCOND
360 INTEGER IPIV( * ), IWORK( * )
361 DOUBLE PRECISION A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
362 $ berr( * ), c( * ), ferr( * ), r( * ),
363 $ work( * ), x( ldx, * )
369 DOUBLE PRECISION ZERO, ONE
370 PARAMETER ( ZERO = 0.0d+0, one = 1.0d+0 )
373 LOGICAL COLEQU, EQUIL, NOFACT, NOTRAN, ROWEQU
376 DOUBLE PRECISION AMAX, ANORM, BIGNUM, COLCND, RCMAX, RCMIN,
377 $ rowcnd, rpvgrw, smlnum
381 DOUBLE PRECISION DLAMCH, DLANGE, DLANTR
382 EXTERNAL lsame, dlamch, dlange, dlantr
394 nofact = lsame( fact,
'N' )
395 equil = lsame( fact,
'E' )
396 notran = lsame( trans,
'N' )
397 IF( nofact .OR. equil )
THEN
402 rowequ = lsame( equed,
'R' ) .OR. lsame( equed,
'B' )
403 colequ = lsame( equed,
'C' ) .OR. lsame( equed,
'B' )
404 smlnum = dlamch(
'Safe minimum' )
405 bignum = one / smlnum
410 IF( .NOT.nofact .AND. .NOT.equil .AND. .NOT.lsame( fact,
'F' ) )
413 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
414 $ lsame( trans,
'C' ) )
THEN
416 ELSE IF( n.LT.0 )
THEN
418 ELSE IF( nrhs.LT.0 )
THEN
420 ELSE IF( lda.LT.max( 1, n ) )
THEN
422 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
424 ELSE IF( lsame( fact,
'F' ) .AND. .NOT.
425 $ ( rowequ .OR. colequ .OR. lsame( equed,
'N' ) ) )
THEN
432 rcmin = min( rcmin, r( j ) )
433 rcmax = max( rcmax, r( j ) )
435 IF( rcmin.LE.zero )
THEN
437 ELSE IF( n.GT.0 )
THEN
438 rowcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
443 IF( colequ .AND. info.EQ.0 )
THEN
447 rcmin = min( rcmin, c( j ) )
448 rcmax = max( rcmax, c( j ) )
450 IF( rcmin.LE.zero )
THEN
452 ELSE IF( n.GT.0 )
THEN
453 colcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
459 IF( ldb.LT.max( 1, n ) )
THEN
461 ELSE IF( ldx.LT.max( 1, n ) )
THEN
468 CALL xerbla(
'DGESVX', -info )
476 CALL dgeequ( n, n, a, lda, r, c, rowcnd, colcnd, amax, infequ )
477 IF( infequ.EQ.0 )
THEN
481 CALL dlaqge( n, n, a, lda, r, c, rowcnd, colcnd, amax,
483 rowequ = lsame( equed,
'R' ) .OR. lsame( equed,
'B' )
484 colequ = lsame( equed,
'C' ) .OR. lsame( equed,
'B' )
494 b( i, j ) = r( i )*b( i, j )
498 ELSE IF( colequ )
THEN
501 b( i, j ) = c( i )*b( i, j )
506 IF( nofact .OR. equil )
THEN
510 CALL dlacpy(
'Full', n, n, a, lda, af, ldaf )
511 CALL dgetrf( n, n, af, ldaf, ipiv, info )
520 rpvgrw = dlantr(
'M',
'U',
'N', info, info, af, ldaf,
522 IF( rpvgrw.EQ.zero )
THEN
525 rpvgrw = dlange(
'M', n, info, a, lda, work ) / rpvgrw
541 anorm = dlange( norm, n, n, a, lda, work )
542 rpvgrw = dlantr(
'M',
'U',
'N', n, n, af, ldaf, work )
543 IF( rpvgrw.EQ.zero )
THEN
546 rpvgrw = dlange(
'M', n, n, a, lda, work ) / rpvgrw
551 CALL dgecon( norm, n, af, ldaf, anorm, rcond, work, iwork, info )
555 CALL dlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
556 CALL dgetrs( trans, n, nrhs, af, ldaf, ipiv, x, ldx, info )
561 CALL dgerfs( trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x,
562 $ ldx, ferr, berr, work, iwork, info )
571 x( i, j ) = c( i )*x( i, j )
575 ferr( j ) = ferr( j ) / colcnd
578 ELSE IF( rowequ )
THEN
581 x( i, j ) = r( i )*x( i, j )
585 ferr( j ) = ferr( j ) / rowcnd
593 IF( rcond.LT.dlamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine dgecon(norm, n, a, lda, anorm, rcond, work, iwork, info)
DGECON
subroutine dgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)
DGEEQU
subroutine dgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DGERFS
subroutine dgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DGESVX computes the solution to system of linear equations A * X = B for GE matrices
subroutine dgetrf(m, n, a, lda, ipiv, info)
DGETRF
subroutine dgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
DGETRS
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.
subroutine dlaqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)
DLAQGE scales a general rectangular matrix, using row and column scaling factors computed by sgeequ.