435 SUBROUTINE sgbrfsx( TRANS, EQUED, N, KL, KU, NRHS, AB, LDAB, AFB,
436 $ LDAFB, IPIV, R, C, B, LDB, X, LDX, RCOND,
437 $ BERR, N_ERR_BNDS, ERR_BNDS_NORM,
438 $ ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, IWORK,
446 CHARACTER TRANS, EQUED
447 INTEGER INFO, LDAB, LDAFB, LDB, LDX, N, KL, KU, NRHS,
448 $ NPARAMS, N_ERR_BNDS
452 INTEGER IPIV( * ), IWORK( * )
453 REAL AB( LDAB, * ), AFB( LDAFB, * ), B( LDB, * ),
454 $ X( LDX , * ),WORK( * )
455 REAL R( * ), C( * ), PARAMS( * ), BERR( * ),
456 $ err_bnds_norm( nrhs, * ),
457 $ err_bnds_comp( nrhs, * )
464 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
465 REAL ITREF_DEFAULT, ITHRESH_DEFAULT,
466 $ COMPONENTWISE_DEFAULT
467 REAL RTHRESH_DEFAULT, DZTHRESH_DEFAULT
468 parameter( itref_default = 1.0 )
469 parameter( ithresh_default = 10.0 )
470 parameter( componentwise_default = 1.0 )
471 parameter( rthresh_default = 0.5 )
472 parameter( dzthresh_default = 0.25 )
473 INTEGER LA_LINRX_ITREF_I, LA_LINRX_ITHRESH_I,
475 parameter( la_linrx_itref_i = 1,
476 $ la_linrx_ithresh_i = 2 )
477 parameter( la_linrx_cwise_i = 3 )
478 INTEGER LA_LINRX_TRUST_I, LA_LINRX_ERR_I,
480 parameter( la_linrx_trust_i = 1, la_linrx_err_i = 2 )
481 parameter( la_linrx_rcond_i = 3 )
485 LOGICAL ROWEQU, COLEQU, NOTRAN
486 INTEGER J, TRANS_TYPE, PREC_TYPE, REF_TYPE
488 REAL ANORM, RCOND_TMP
489 REAL ILLRCOND_THRESH, ERR_LBND, CWISE_WRONG
492 REAL RTHRESH, UNSTABLE_THRESH
504 REAL SLAMCH, SLANGB, SLA_GBRCOND
506 INTEGER ILATRANS, ILAPREC
513 trans_type = ilatrans( trans )
514 ref_type = int( itref_default )
515 IF ( nparams .GE. la_linrx_itref_i )
THEN
516 IF ( params( la_linrx_itref_i ) .LT. 0.0 )
THEN
517 params( la_linrx_itref_i ) = itref_default
519 ref_type = params( la_linrx_itref_i )
525 illrcond_thresh = real( n ) * slamch(
'Epsilon' )
526 ithresh = int( ithresh_default )
527 rthresh = rthresh_default
528 unstable_thresh = dzthresh_default
529 ignore_cwise = componentwise_default .EQ. 0.0
531 IF ( nparams.GE.la_linrx_ithresh_i )
THEN
532 IF ( params( la_linrx_ithresh_i ).LT.0.0 )
THEN
533 params( la_linrx_ithresh_i ) = ithresh
535 ithresh = int( params( la_linrx_ithresh_i ) )
538 IF ( nparams.GE.la_linrx_cwise_i )
THEN
539 IF ( params( la_linrx_cwise_i ).LT.0.0 )
THEN
540 IF ( ignore_cwise )
THEN
541 params( la_linrx_cwise_i ) = 0.0
543 params( la_linrx_cwise_i ) = 1.0
546 ignore_cwise = params( la_linrx_cwise_i ) .EQ. 0.0
549 IF ( ref_type .EQ. 0 .OR. n_err_bnds .EQ. 0 )
THEN
551 ELSE IF ( ignore_cwise )
THEN
557 notran = lsame( trans,
'N' )
558 rowequ = lsame( equed,
'R' ) .OR. lsame( equed,
'B' )
559 colequ = lsame( equed,
'C' ) .OR. lsame( equed,
'B' )
563 IF( trans_type.EQ.-1 )
THEN
565 ELSE IF( .NOT.rowequ .AND. .NOT.colequ .AND.
566 $ .NOT.lsame( equed,
'N' ) )
THEN
568 ELSE IF( n.LT.0 )
THEN
570 ELSE IF( kl.LT.0 )
THEN
572 ELSE IF( ku.LT.0 )
THEN
574 ELSE IF( nrhs.LT.0 )
THEN
576 ELSE IF( ldab.LT.kl+ku+1 )
THEN
578 ELSE IF( ldafb.LT.2*kl+ku+1 )
THEN
580 ELSE IF( ldb.LT.max( 1, n ) )
THEN
582 ELSE IF( ldx.LT.max( 1, n ) )
THEN
586 CALL xerbla(
'SGBRFSX', -info )
592 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
596 IF ( n_err_bnds .GE. 1 )
THEN
597 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
598 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
600 IF ( n_err_bnds .GE. 2 )
THEN
601 err_bnds_norm( j, la_linrx_err_i ) = 0.0
602 err_bnds_comp( j, la_linrx_err_i ) = 0.0
604 IF ( n_err_bnds .GE. 3 )
THEN
605 err_bnds_norm( j, la_linrx_rcond_i ) = 1.0
606 err_bnds_comp( j, la_linrx_rcond_i ) = 1.0
617 IF ( n_err_bnds .GE. 1 )
THEN
618 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
619 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
621 IF ( n_err_bnds .GE. 2 )
THEN
622 err_bnds_norm( j, la_linrx_err_i ) = 1.0
623 err_bnds_comp( j, la_linrx_err_i ) = 1.0
625 IF ( n_err_bnds .GE. 3 )
THEN
626 err_bnds_norm( j, la_linrx_rcond_i ) = 0.0
627 err_bnds_comp( j, la_linrx_rcond_i ) = 0.0
639 anorm = slangb( norm, n, kl, ku, ab, ldab, work )
640 CALL sgbcon( norm, n, kl, ku, afb, ldafb, ipiv, anorm, rcond,
641 $ work, iwork, info )
645 IF ( ref_type .NE. 0 .AND. info .EQ. 0 )
THEN
647 prec_type = ilaprec(
'D' )
651 $ nrhs, ab, ldab, afb, ldafb, ipiv, colequ, c, b,
652 $ ldb, x, ldx, berr, n_norms, err_bnds_norm,
653 $ err_bnds_comp, work( n+1 ), work( 1 ), work( 2*n+1 ),
654 $ work( 1 ), rcond, ithresh, rthresh, unstable_thresh,
655 $ ignore_cwise, info )
658 $ nrhs, ab, ldab, afb, ldafb, ipiv, rowequ, r, b,
659 $ ldb, x, ldx, berr, n_norms, err_bnds_norm,
660 $ err_bnds_comp, work( n+1 ), work( 1 ), work( 2*n+1 ),
661 $ work( 1 ), rcond, ithresh, rthresh, unstable_thresh,
662 $ ignore_cwise, info )
666 err_lbnd = max( 10.0, sqrt( real( n ) ) ) * slamch(
'Epsilon' )
667 IF ( n_err_bnds .GE. 1 .AND. n_norms .GE. 1 )
THEN
671 IF ( colequ .AND. notran )
THEN
672 rcond_tmp = sla_gbrcond( trans, n, kl, ku, ab, ldab, afb,
673 $ ldafb, ipiv, -1, c, info, work, iwork )
674 ELSE IF ( rowequ .AND. .NOT. notran )
THEN
675 rcond_tmp = sla_gbrcond( trans, n, kl, ku, ab, ldab, afb,
676 $ ldafb, ipiv, -1, r, info, work, iwork )
678 rcond_tmp = sla_gbrcond( trans, n, kl, ku, ab, ldab, afb,
679 $ ldafb, ipiv, 0, r, info, work, iwork )
685 IF ( n_err_bnds .GE. la_linrx_err_i
686 $ .AND. err_bnds_norm( j, la_linrx_err_i ) .GT. 1.0 )
687 $ err_bnds_norm( j, la_linrx_err_i ) = 1.0
691 IF ( rcond_tmp .LT. illrcond_thresh )
THEN
692 err_bnds_norm( j, la_linrx_err_i ) = 1.0
693 err_bnds_norm( j, la_linrx_trust_i ) = 0.0
694 IF ( info .LE. n ) info = n + j
695 ELSE IF ( err_bnds_norm( j, la_linrx_err_i ) .LT. err_lbnd )
697 err_bnds_norm( j, la_linrx_err_i ) = err_lbnd
698 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
703 IF ( n_err_bnds .GE. la_linrx_rcond_i )
THEN
704 err_bnds_norm( j, la_linrx_rcond_i ) = rcond_tmp
710 IF (n_err_bnds .GE. 1 .AND. n_norms .GE. 2)
THEN
720 cwise_wrong = sqrt( slamch(
'Epsilon' ) )
722 IF ( err_bnds_comp( j, la_linrx_err_i ) .LT. cwise_wrong )
724 rcond_tmp = sla_gbrcond( trans, n, kl, ku, ab, ldab, afb,
725 $ ldafb, ipiv, 1, x( 1, j ), info, work, iwork )
732 IF ( n_err_bnds .GE. la_linrx_err_i
733 $ .AND. err_bnds_comp( j, la_linrx_err_i ) .GT. 1.0 )
734 $ err_bnds_comp( j, la_linrx_err_i ) = 1.0
738 IF ( rcond_tmp .LT. illrcond_thresh )
THEN
739 err_bnds_comp( j, la_linrx_err_i ) = 1.0
740 err_bnds_comp( j, la_linrx_trust_i ) = 0.0
741 IF ( params( la_linrx_cwise_i ) .EQ. 1.0
742 $ .AND. info.LT.n + j ) info = n + j
743 ELSE IF ( err_bnds_comp( j, la_linrx_err_i )
744 $ .LT. err_lbnd )
THEN
745 err_bnds_comp( j, la_linrx_err_i ) = err_lbnd
746 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
751 IF ( n_err_bnds .GE. la_linrx_rcond_i )
THEN
752 err_bnds_comp( j, la_linrx_rcond_i ) = rcond_tmp
subroutine xerbla(srname, info)
subroutine sgbcon(norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond, work, iwork, info)
SGBCON
subroutine sgbrfsx(trans, equed, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, r, c, b, ldb, x, ldx, rcond, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
SGBRFSX
integer function ilaprec(prec)
ILAPREC
integer function ilatrans(trans)
ILATRANS
real function sla_gbrcond(trans, n, kl, ku, ab, ldab, afb, ldafb, ipiv, cmode, c, info, work, iwork)
SLA_GBRCOND estimates the Skeel condition number for a general banded matrix.
subroutine sla_gbrfsx_extended(prec_type, trans_type, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, colequ, c, b, ldb, y, ldy, berr_out, n_norms, err_bnds_norm, err_bnds_comp, res, ayb, dy, y_tail, rcond, ithresh, rthresh, dz_ub, ignore_cwise, info)
SLA_GBRFSX_EXTENDED improves the computed solution to a system of linear equations for general banded...
real function slamch(cmach)
SLAMCH
real function slangb(norm, n, kl, ku, ab, ldab, work)
SLANGB returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
logical function lsame(ca, cb)
LSAME