410 SUBROUTINE sgerfsx( TRANS, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV,
411 $ R, C, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS,
412 $ ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS,
413 $ WORK, IWORK, INFO )
420 CHARACTER TRANS, EQUED
421 INTEGER INFO, LDA, LDAF, LDB, LDX, N, NRHS, NPARAMS,
426 INTEGER IPIV( * ), IWORK( * )
427 REAL A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
428 $ X( LDX , * ), WORK( * )
429 REAL R( * ), C( * ), PARAMS( * ), BERR( * ),
430 $ err_bnds_norm( nrhs, * ),
431 $ err_bnds_comp( nrhs, * )
438 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
439 REAL ITREF_DEFAULT, ITHRESH_DEFAULT,
440 $ componentwise_default
441 REAL RTHRESH_DEFAULT, DZTHRESH_DEFAULT
442 parameter( itref_default = 1.0 )
443 parameter( ithresh_default = 10.0 )
444 parameter( componentwise_default = 1.0 )
445 parameter( rthresh_default = 0.5 )
446 parameter( dzthresh_default = 0.25 )
449 parameter( la_linrx_itref_i = 1,
450 $ la_linrx_ithresh_i = 2 )
451 parameter( la_linrx_cwise_i = 3 )
452 INTEGER , LA_LINRX_ERR_I,
454 parameter( la_linrx_trust_i = 1, la_linrx_err_i = 2 )
455 parameter( la_linrx_rcond_i = 3 )
459 LOGICAL ROWEQU, COLEQU, NOTRAN
460 INTEGER J, TRANS_TYPE, PREC_TYPE, REF_TYPE
462 REAL ANORM, RCOND_TMP
463 REAL ILLRCOND_THRESH, ERR_LBND, CWISE_WRONG
466 REAL RTHRESH, UNSTABLE_THRESH
477 REAL SLAMCH, SLANGE, SLA_GERCOND
479 INTEGER ILATRANS, ILAPREC
486 trans_type = ilatrans( trans )
487 ref_type = int( itref_default )
488 IF ( nparams .GE. la_linrx_itref_i )
THEN
489 IF ( params( la_linrx_itref_i ) .LT. 0.0 )
THEN
490 params( la_linrx_itref_i ) = itref_default
492 ref_type = params( la_linrx_itref_i )
498 illrcond_thresh = real( n ) * slamch(
'Epsilon' )
499 ithresh = int( ithresh_default )
500 rthresh = rthresh_default
501 unstable_thresh = dzthresh_default
502 ignore_cwise = componentwise_default .EQ. 0.0
504 IF ( nparams.GE.la_linrx_ithresh_i )
THEN
505 IF ( params( la_linrx_ithresh_i ).LT.0.0 )
THEN
506 params( la_linrx_ithresh_i ) = ithresh
508 ithresh = int( params( la_linrx_ithresh_i ) )
511 IF ( nparams.GE.la_linrx_cwise_i )
THEN
512 IF ( params( la_linrx_cwise_i ).LT.0.0 )
THEN
513 IF ( ignore_cwise )
THEN
514 params( la_linrx_cwise_i ) = 0.0
516 params( la_linrx_cwise_i ) = 1.0
519 ignore_cwise = params( la_linrx_cwise_i ) .EQ. 0.0
522 IF ( ref_type .EQ. 0 .OR. n_err_bnds .EQ. 0 )
THEN
524 ELSE IF ( ignore_cwise )
THEN
530 notran = lsame( trans,
'N' )
531 rowequ = lsame( equed,
'R' ) .OR. lsame( equed,
'B' )
532 colequ = lsame( equed,
'C' ) .OR. lsame( equed,
'B' )
536 IF( trans_type.EQ.-1 )
THEN
538 ELSE IF( .NOT.rowequ .AND. .NOT.colequ .AND.
539 $ .NOT.lsame( equed,
'N' ) )
THEN
541 ELSE IF( n.LT.0 )
THEN
543 ELSE IF( nrhs.LT.0 )
THEN
545 ELSE IF( lda.LT.
max( 1, n ) )
THEN
549 ELSE IF( ldb.LT.
max( 1, n ) )
THEN
551 ELSE IF( ldx.LT.
max( 1, n ) )
THEN
555 CALL xerbla(
'SGERFSX', -info )
561 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
565 IF ( n_err_bnds .GE. 1 )
THEN
566 err_bnds_norm( j, la_linrx_trust_i) = 1.0
567 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
569 IF ( n_err_bnds .GE. 2 )
THEN
570 err_bnds_norm( j, la_linrx_err_i) = 0.0
571 err_bnds_comp( j, la_linrx_err_i ) = 0.0
573 IF ( n_err_bnds .GE. 3 )
THEN
574 err_bnds_norm( j, la_linrx_rcond_i) = 1.0
575 err_bnds_comp( j, la_linrx_rcond_i ) = 1.0
586 IF ( n_err_bnds .GE. 1 )
THEN
587 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
588 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
590 IF ( n_err_bnds .GE. 2 )
THEN
591 err_bnds_norm( j, la_linrx_err_i ) = 1.0
592 err_bnds_comp( j, la_linrx_err_i ) = 1.0
594 IF ( n_err_bnds .GE. 3 )
THEN
595 err_bnds_norm( j, la_linrx_rcond_i ) = 0.0
596 err_bnds_comp( j, la_linrx_rcond_i ) = 0.0
608 anorm = slange( norm, n, n, a, lda, work )
609 CALL sgecon( norm, n, af, ldaf, anorm, rcond, work, iwork, info )
613 IF ( ref_type .NE. 0 )
THEN
615 prec_type = ilaprec(
'D' )
619 $ nrhs, a, lda, af, ldaf, ipiv, colequ, c, b,
620 $ ldb, x, ldx, berr, n_norms, err_bnds_norm,
621 $ err_bnds_comp, work(n+1), work(1), work(2*n+1),
622 $ work(1), rcond, ithresh, rthresh, unstable_thresh,
623 $ ignore_cwise, info )
626 $ nrhs, a, lda, af, ldaf, ipiv, rowequ, r, b,
627 $ ldb, x, ldx, berr, n_norms, err_bnds_norm,
628 $ err_bnds_comp, work(n+1), work(1), work(2*n+1),
629 $ work(1), rcond, ithresh, rthresh, unstable_thresh,
630 $ ignore_cwise, info )
634 err_lbnd =
max( 10.0, sqrt( real( n ) ) ) * slamch(
'Epsilon' )
635 IF ( n_err_bnds .GE. 1 .AND. n_norms .GE. 1 )
THEN
639 IF ( colequ .AND. notran )
THEN
640 rcond_tmp = sla_gercond( trans, n, a, lda, af, ldaf
641 $ -1, c, info, work, iwork )
642 ELSE IF ( rowequ .AND. .NOT. notran )
THEN
643 rcond_tmp = sla_gercond( trans, n, a, lda, af, ldaf, ipiv,
644 $ -1, r, info, work, iwork )
646 rcond_tmp = sla_gercond( trans, n, a, lda, af, ldaf, ipiv,
647 $ 0, r, info, work, iwork )
653 IF ( n_err_bnds .GE. la_linrx_err_i
654 $ .AND. err_bnds_norm( j, la_linrx_err_i ) .GT. 1.0 )
655 $ err_bnds_norm( j, la_linrx_err_i ) = 1.0
659 IF ( rcond_tmp .LT. illrcond_thresh )
THEN
660 err_bnds_norm( j, la_linrx_err_i ) = 1.0
661 err_bnds_norm( j, la_linrx_trust_i ) = 0.0
662 IF ( info .LE. n ) info = n + j
663 ELSE IF ( err_bnds_norm( j, la_linrx_err_i ) .LT. err_lbnd )
665 err_bnds_norm( j, la_linrx_err_i ) = err_lbnd
666 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
671 IF ( n_err_bnds .GE. la_linrx_rcond_i )
THEN
672 err_bnds_norm( j, la_linrx_rcond_i ) = rcond_tmp
677 IF ( n_err_bnds .GE. 1 .AND. n_norms .GE. 2 )
THEN
687 cwise_wrong = sqrt( slamch(
'Epsilon' ) )
689 IF ( err_bnds_comp( j, la_linrx_err_i ) .LT. cwise_wrong )
692 $ ipiv, 1, x(1,j), info, work, iwork )
699 IF ( n_err_bnds .GE. la_linrx_err_i
701 $ err_bnds_comp( j, la_linrx_err_i ) = 1.0
706 err_bnds_comp( j, la_linrx_err_i ) = 1.0
707 err_bnds_comp( j, la_linrx_trust_i ) = 0.0
708 IF ( params( la_linrx_cwise_i ) .EQ. 1.0
709 $ .AND. info.LT.n + j ) info = n + j
710 ELSE IF ( err_bnds_comp( j, la_linrx_err_i )
712 err_bnds_comp( j, la_linrx_err_i ) = err_lbnd
713 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
718 IF ( n_err_bnds .GE. la_linrx_rcond_i )
THEN
719 err_bnds_comp( j, la_linrx_rcond_i ) = rcond_tmp