309 SUBROUTINE dppsvx( FACT, UPLO, N, NRHS, AP, AFP, EQUED, S, B, LDB,
310 $ X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO )
317 CHARACTER EQUED, FACT, UPLO
318 INTEGER INFO, LDB, LDX, N, NRHS
319 DOUBLE PRECISION RCOND
323 DOUBLE PRECISION AFP( * ), AP( * ), B( LDB, * ), BERR( * ),
324 $ ferr( * ), s( * ), work( * ), x( ldx, * )
330 DOUBLE PRECISION ZERO, ONE
331 parameter( zero = 0.0d+0, one = 1.0d+0 )
334 LOGICAL EQUIL, NOFACT, RCEQU
336 DOUBLE PRECISION AMAX, ANORM, BIGNUM, SCOND, SMAX, SMIN, SMLNUM
340 DOUBLE PRECISION DLAMCH, DLANSP
341 EXTERNAL lsame, dlamch, dlansp
353 nofact = lsame( fact,
'N' )
354 equil = lsame( fact,
'E' )
355 IF( nofact .OR. equil )
THEN
359 rcequ = lsame( equed,
'Y' )
360 smlnum = dlamch(
'Safe minimum' )
361 bignum = one / smlnum
366 IF( .NOT.nofact .AND. .NOT.equil .AND. .NOT.lsame( fact,
'F' ) )
369 ELSE IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
372 ELSE IF( n.LT.0 )
THEN
374 ELSE IF( nrhs.LT.0 )
THEN
376 ELSE IF( lsame( fact,
'F' ) .AND. .NOT.
377 $ ( rcequ .OR. lsame( equed,
'N' ) ) )
THEN
384 smin = min( smin, s( j ) )
385 smax = max( smax, s( j ) )
387 IF( smin.LE.zero )
THEN
389 ELSE IF( n.GT.0 )
THEN
390 scond = max( smin, smlnum ) / min( smax, bignum )
396 IF( ldb.LT.max( 1, n ) )
THEN
398 ELSE IF( ldx.LT.max( 1, n ) )
THEN
405 CALL xerbla(
'DPPSVX', -info )
413 CALL dppequ( uplo, n, ap, s, scond, amax, infequ )
414 IF( infequ.EQ.0 )
THEN
418 CALL dlaqsp( uplo, n, ap, s, scond, amax, equed )
419 rcequ = lsame( equed,
'Y' )
428 b( i, j ) = s( i )*b( i, j )
433 IF( nofact .OR. equil )
THEN
437 CALL dcopy( n*( n+1 ) / 2, ap, 1, afp, 1 )
438 CALL dpptrf( uplo, n, afp, info )
450 anorm = dlansp(
'I', uplo, n, ap, work )
454 CALL dppcon( uplo, n, afp, anorm, rcond, work, iwork, info )
458 CALL dlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
459 CALL dpptrs( uplo, n, nrhs, afp, x, ldx, info )
464 CALL dpprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr,
465 $ work, iwork, info )
473 x( i, j ) = s( i )*x( i, j )
477 ferr( j ) = ferr( j ) / scond
483 IF( rcond.LT.dlamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.
subroutine dlaqsp(uplo, n, ap, s, scond, amax, equed)
DLAQSP scales a symmetric/Hermitian matrix in packed storage, using scaling factors computed by sppeq...
subroutine dppcon(uplo, n, ap, anorm, rcond, work, iwork, info)
DPPCON
subroutine dppequ(uplo, n, ap, s, scond, amax, info)
DPPEQU
subroutine dpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DPPRFS
subroutine dppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
subroutine dpptrf(uplo, n, ap, info)
DPPTRF
subroutine dpptrs(uplo, n, nrhs, ap, b, ldb, info)
DPPTRS