346 SUBROUTINE sgesvx( 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
360 INTEGER IPIV( * ), IWORK( * )
361 REAL A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
362 $ berr( * ), c( * ), ferr( * ), r( * ),
363 $ work( * ), x( ldx, * )
370 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
373 LOGICAL COLEQU, EQUIL, NOFACT, NOTRAN, ROWEQU
376 REAL AMAX, ANORM, BIGNUM, COLCND, RCMAX, RCMIN,
377 $ rowcnd, rpvgrw, smlnum
381 REAL SLAMCH, SLANGE, SLANTR
382 EXTERNAL lsame, slamch, slange, slantr
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 = slamch(
'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(
'SGESVX', -info )
476 CALL sgeequ( n, n, a, lda, r, c, rowcnd, colcnd, amax, infequ )
477 IF( infequ.EQ.0 )
THEN
481 CALL slaqge( 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 slacpy(
'Full', n, n, a, lda, af, ldaf )
511 CALL sgetrf( n, n, af, ldaf, ipiv, info )
520 rpvgrw = slantr(
'M',
'U',
'N', info, info, af, ldaf,
522 IF( rpvgrw.EQ.zero )
THEN
525 rpvgrw = slange(
'M', n, info, a, lda, work ) / rpvgrw
541 anorm = slange( norm, n, n, a, lda, work )
542 rpvgrw = slantr(
'M',
'U',
'N', n, n, af, ldaf, work )
543 IF( rpvgrw.EQ.zero )
THEN
546 rpvgrw = slange(
'M', n, n, a, lda, work ) / rpvgrw
551 CALL sgecon( norm, n, af, ldaf, anorm, rcond, work, iwork, info )
555 CALL slacpy(
'Full', n, nrhs, b, ldb, x, ldx )
556 CALL sgetrs( trans, n, nrhs, af, ldaf, ipiv, x, ldx, info )
561 CALL sgerfs( 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
591 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine sgecon(norm, n, a, lda, anorm, rcond, work, iwork, info)
SGECON
subroutine sgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)
SGEEQU
subroutine sgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SGERFS
subroutine sgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
SGESVX computes the solution to system of linear equations A * X = B for GE matrices
subroutine sgetrf(m, n, a, lda, ipiv, info)
SGETRF
subroutine sgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
SGETRS
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine slaqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)
SLAQGE scales a general rectangular matrix, using row and column scaling factors computed by sgeequ.