307      SUBROUTINE sppsvx( FACT, UPLO, N, NRHS, AP, AFP, EQUED, S, B,
 
  309     $                   X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO )
 
  316      CHARACTER          EQUED, FACT, UPLO
 
  317      INTEGER            INFO, LDB, LDX, N, NRHS
 
  322      REAL               AFP( * ), AP( * ), B( LDB, * ), BERR( * ),
 
  323     $                   ferr( * ), s( * ), work( * ), x( ldx, * )
 
  330      PARAMETER          ( ZERO = 0.0e+0, one = 1.0e+0 )
 
  333      LOGICAL            EQUIL, NOFACT, RCEQU
 
  335      REAL               AMAX, ANORM, BIGNUM, SCOND, SMAX, SMIN, SMLNUM
 
  340      EXTERNAL           lsame, slamch, slansp
 
  353      nofact = lsame( fact, 
'N' )
 
  354      equil = lsame( fact, 
'E' )
 
  355      IF( nofact .OR. equil ) 
THEN 
  359         rcequ = lsame( equed, 
'Y' )
 
  360         smlnum = slamch( 
'Safe minimum' )
 
  361         bignum = one / smlnum
 
  366      IF( .NOT.nofact .AND.
 
  368     $    .NOT.lsame( fact, 
'F' ) )
 
  371      ELSE IF( .NOT.lsame( uplo, 
'U' ) .AND.
 
  372     $         .NOT.lsame( uplo, 
'L' ) )
 
  375      ELSE IF( n.LT.0 ) 
THEN 
  377      ELSE IF( nrhs.LT.0 ) 
THEN 
  379      ELSE IF( lsame( fact, 
'F' ) .AND. .NOT.
 
  380     $         ( rcequ .OR. lsame( equed, 
'N' ) ) ) 
THEN 
  387               smin = min( smin, s( j ) )
 
  388               smax = max( smax, s( j ) )
 
  390            IF( smin.LE.zero ) 
THEN 
  392            ELSE IF( n.GT.0 ) 
THEN 
  393               scond = max( smin, smlnum ) / min( smax, bignum )
 
  399            IF( ldb.LT.max( 1, n ) ) 
THEN 
  401            ELSE IF( ldx.LT.max( 1, n ) ) 
THEN 
  408         CALL xerbla( 
'SPPSVX', -info )
 
  416         CALL sppequ( uplo, n, ap, s, scond, amax, infequ )
 
  417         IF( infequ.EQ.0 ) 
THEN 
  421            CALL slaqsp( uplo, n, ap, s, scond, amax, equed )
 
  422            rcequ = lsame( equed, 
'Y' )
 
  431               b( i, j ) = s( i )*b( i, j )
 
  436      IF( nofact .OR. equil ) 
THEN 
  440         CALL scopy( n*( n+1 ) / 2, ap, 1, afp, 1 )
 
  441         CALL spptrf( uplo, n, afp, info )
 
  453      anorm = slansp( 
'I', uplo, n, ap, work )
 
  457      CALL sppcon( uplo, n, afp, anorm, rcond, work, iwork, info )
 
  461      CALL slacpy( 
'Full', n, nrhs, b, ldb, x, ldx )
 
  462      CALL spptrs( uplo, n, nrhs, afp, x, ldx, info )
 
  467      CALL spprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr,
 
  469     $             work, iwork, info )
 
  477               x( i, j ) = s( i )*x( i, j )
 
  481            ferr( j ) = ferr( j ) / scond
 
  487      IF( rcond.LT.slamch( 
'Epsilon' ) )
 
 
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine slaqsp(uplo, n, ap, s, scond, amax, equed)
SLAQSP scales a symmetric/Hermitian matrix in packed storage, using scaling factors computed by sppeq...
subroutine spprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPPRFS
subroutine sppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
SPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices