339 SUBROUTINE cpbsvx( FACT, UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB,
340 $ EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR,
341 $ WORK, RWORK, INFO )
348 CHARACTER EQUED, FACT, UPLO
349 INTEGER INFO, KD, LDAB, LDAFB, LDB, LDX, N, NRHS
353 REAL BERR( * ), FERR( * ), RWORK( * ), S( * )
354 COMPLEX AB( LDAB, * ), AFB( LDAFB, * ), B( LDB, * ),
355 $ work( * ), x( ldx, * )
362 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
365 LOGICAL EQUIL, NOFACT, RCEQU, UPPER
366 INTEGER I, INFEQU, J, J1, J2
367 REAL AMAX, ANORM, BIGNUM, SCOND, SMAX, SMIN, SMLNUM
372 EXTERNAL lsame, clanhb, slamch
384 nofact = lsame( fact,
'N' )
385 equil = lsame( fact,
'E' )
386 upper = lsame( uplo,
'U' )
387 IF( nofact .OR. equil )
THEN
391 rcequ = lsame( equed,
'Y' )
392 smlnum = slamch(
'Safe minimum' )
393 bignum = one / smlnum
398 IF( .NOT.nofact .AND. .NOT.equil .AND. .NOT.lsame( fact,
'F' ) )
401 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
403 ELSE IF( n.LT.0 )
THEN
405 ELSE IF( kd.LT.0 )
THEN
407 ELSE IF( nrhs.LT.0 )
THEN
409 ELSE IF( ldab.LT.kd+1 )
THEN
411 ELSE IF( ldafb.LT.kd+1 )
THEN
413 ELSE IF( lsame( fact,
'F' ) .AND. .NOT.
414 $ ( rcequ .OR. lsame( equed,
'N' ) ) )
THEN
421 smin = min( smin, s( j ) )
422 smax = max( smax, s( j ) )
424 IF( smin.LE.zero )
THEN
426 ELSE IF( n.GT.0 )
THEN
427 scond = max( smin, smlnum ) / min( smax, bignum )
433 IF( ldb.LT.max( 1, n ) )
THEN
435 ELSE IF( ldx.LT.max( 1, n ) )
THEN
442 CALL xerbla(
'CPBSVX', -info )
450 CALL cpbequ( uplo, n, kd, ab, ldab, s, scond, amax, infequ )
451 IF( infequ.EQ.0 )
THEN
455 CALL claqhb( uplo, n, kd, ab, ldab, s, scond, amax, equed )
456 rcequ = lsame( equed,
'Y' )
465 b( i, j ) = s( i )*b( i, j )
470 IF( nofact .OR. equil )
THEN
477 CALL ccopy( j-j1+1, ab( kd+1-j+j1, j ), 1,
478 $ afb( kd+1-j+j1, j ), 1 )
483 CALL ccopy( j2-j+1, ab( 1, j ), 1, afb( 1, j ), 1 )
487 CALL cpbtrf( uplo, n, kd, afb, ldafb, info )
499 anorm = clanhb(
'1', uplo, n, kd, ab, ldab, rwork )
503 CALL cpbcon( uplo, n, kd, afb, ldafb, anorm, rcond, work, rwork,
508 CALL clacpy(
'Full', n, nrhs, b, ldb, x, ldx )
509 CALL cpbtrs( uplo, n, kd, nrhs, afb, ldafb, x, ldx, info )
514 CALL cpbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x,
515 $ ldx, ferr, berr, work, rwork, info )
523 x( i, j ) = s( i )*x( i, j )
527 ferr( j ) = ferr( j ) / scond
533 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine claqhb(uplo, n, kd, ab, ldab, s, scond, amax, equed)
CLAQHB scales a Hermitian band matrix, using scaling factors computed by cpbequ.
subroutine cpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, rwork, info)
CPBCON
subroutine cpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)
CPBEQU
subroutine cpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CPBRFS
subroutine cpbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices
subroutine cpbtrf(uplo, n, kd, ab, ldab, info)
CPBTRF
subroutine cpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
CPBTRS