340 SUBROUTINE dpbsvx( FACT, UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB,
341 $ EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR,
342 $ WORK, IWORK, INFO )
349 CHARACTER EQUED, FACT, UPLO
350 INTEGER INFO, KD, LDAB, LDAFB, LDB, LDX, N, NRHS
351 DOUBLE PRECISION RCOND
355 DOUBLE PRECISION AB( LDAB, * ), AFB( LDAFB, * ), B( LDB, * ),
356 $ berr( * ), ferr( * ), s( * ), work( * ),
363 DOUBLE PRECISION ZERO, ONE
364 PARAMETER ( ZERO = 0.0d+0, one = 1.0d+0 )
367 LOGICAL EQUIL, NOFACT, RCEQU, UPPER
368 INTEGER I, INFEQU, J, J1, J2
369 DOUBLE PRECISION AMAX, ANORM, BIGNUM, SCOND, SMAX, SMIN, SMLNUM
373 DOUBLE PRECISION DLAMCH, DLANSB
374 EXTERNAL lsame, dlamch, dlansb
386 nofact = lsame( fact,
'N' )
387 equil = lsame( fact,
'E' )
388 upper = lsame( uplo,
'U' )
389 IF( nofact .OR. equil )
THEN
393 rcequ = lsame( equed,
'Y' )
394 smlnum = dlamch(
'Safe minimum' )
395 bignum = one / smlnum
400 IF( .NOT.nofact .AND. .NOT.equil .AND. .NOT.lsame( fact,
'F' ) )
403 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
405 ELSE IF( n.LT.0 )
THEN
407 ELSE IF( kd.LT.0 )
THEN
409 ELSE IF( nrhs.LT.0 )
THEN
411 ELSE IF( ldab.LT.kd+1 )
THEN
413 ELSE IF( ldafb.LT.kd+1 )
THEN
415 ELSE IF( lsame( fact,
'F' ) .AND. .NOT.
416 $ ( rcequ .OR. lsame( equed,
'N' ) ) )
THEN
423 smin = min( smin, s( j ) )
424 smax = max( smax, s( j ) )
426 IF( smin.LE.zero )
THEN
428 ELSE IF( n.GT.0 )
THEN
429 scond = max( smin, smlnum ) / min( smax, bignum )
435 IF( ldb.LT.max( 1, n ) )
THEN
437 ELSE IF( ldx.LT.max( 1, n ) )
THEN
444 CALL xerbla(
'DPBSVX', -info )
452 CALL dpbequ( uplo, n, kd, ab, ldab, s, scond, amax, infequ )
453 IF( infequ.EQ.0 )
THEN
457 CALL dlaqsb( uplo, n, kd, ab, ldab, s, scond, amax, equed )
458 rcequ = lsame( equed,
'Y' )
467 b( i, j ) = s( i )*b( i, j )
472 IF( nofact .OR. equil )
THEN
479 CALL dcopy( j-j1+1, ab( kd+1-j+j1, j ), 1,
480 $ afb( kd+1-j+j1, j ), 1 )
485 CALL dcopy( j2-j+1, ab( 1, j ), 1, afb( 1, j ), 1 )
489 CALL dpbtrf( uplo, n, kd, afb, ldafb, info )
501 anorm = dlansb(
'1', uplo, n, kd, ab, ldab, work )
505 CALL dpbcon( uplo, n, kd, afb, ldafb, anorm, rcond, work, iwork,
510 CALL dlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
511 CALL dpbtrs( uplo, n, kd, nrhs, afb, ldafb, x, ldx, info )
516 CALL dpbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x,
517 $ ldx, ferr, berr, work, iwork, info )
525 x( i, j ) = s( i )*x( i, j )
529 ferr( j ) = ferr( j ) / scond
535 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 dlaqsb(uplo, n, kd, ab, ldab, s, scond, amax, equed)
DLAQSB scales a symmetric/Hermitian band matrix, using scaling factors computed by spbequ.
subroutine dpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, iwork, info)
DPBCON
subroutine dpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)
DPBEQU
subroutine dpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DPBRFS
subroutine dpbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices
subroutine dpbtrf(uplo, n, kd, ab, ldab, info)
DPBTRF
subroutine dpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
DPBTRS