398 SUBROUTINE ssyrfsx( UPLO, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV,
399 $ S, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS,
400 $ ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS,
401 $ WORK, IWORK, INFO )
408 CHARACTER UPLO, EQUED
409 INTEGER INFO, LDA, LDAF, LDB, LDX, N, NRHS, NPARAMS,
414 INTEGER IPIV( * ), IWORK( * )
415 REAL A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
416 $ X( LDX, * ), WORK( * )
417 REAL S( * ), PARAMS( * ), BERR( * ),
418 $ err_bnds_norm( nrhs, * ),
419 $ err_bnds_comp( nrhs, * )
426 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
427 REAL ITREF_DEFAULT, ITHRESH_DEFAULT,
428 $ componentwise_default
429 REAL RTHRESH_DEFAULT, DZTHRESH_DEFAULT
430 parameter( itref_default = 1.0 )
431 parameter( ithresh_default = 10.0 )
432 parameter( componentwise_default = 1.0 )
433 parameter( rthresh_default = 0.5 )
434 parameter( dzthresh_default = 0.25 )
435 INTEGER LA_LINRX_ITREF_I, LA_LINRX_ITHRESH_I,
437 parameter( la_linrx_itref_i = 1,
438 $ la_linrx_ithresh_i = 2 )
439 parameter( la_linrx_cwise_i = 3 )
440 INTEGER LA_LINRX_TRUST_I, LA_LINRX_ERR_I,
442 parameter( la_linrx_trust_i = 1, la_linrx_err_i = 2 )
443 parameter( la_linrx_rcond_i = 3 )
448 INTEGER J, PREC_TYPE, REF_TYPE, N_NORMS
449 REAL ANORM, RCOND_TMP
450 REAL ILLRCOND_THRESH, ERR_LBND, CWISE_WRONG
453 REAL RTHRESH, UNSTABLE_THRESH
464 REAL SLAMCH, SLANSY, SLA_SYRCOND
473 ref_type = int( itref_default )
474 IF ( nparams .GE. la_linrx_itref_i )
THEN
475 IF ( params( la_linrx_itref_i ) .LT. 0.0 )
THEN
476 params( la_linrx_itref_i ) = itref_default
478 ref_type = params( la_linrx_itref_i )
484 illrcond_thresh = real( n )*slamch(
'Epsilon' )
485 ithresh = int( ithresh_default )
486 rthresh = rthresh_default
487 unstable_thresh = dzthresh_default
488 ignore_cwise = componentwise_default .EQ. 0.0
490 IF ( nparams.GE.la_linrx_ithresh_i )
THEN
491 IF ( params( la_linrx_ithresh_i ).LT.0.0 )
THEN
492 params( la_linrx_ithresh_i ) = ithresh
494 ithresh = int( params( la_linrx_ithresh_i ) )
497 IF ( nparams.GE.la_linrx_cwise_i )
THEN
498 IF ( params( la_linrx_cwise_i ).LT.0.0 )
THEN
499 IF ( ignore_cwise )
THEN
500 params( la_linrx_cwise_i ) = 0.0
502 params( la_linrx_cwise_i ) = 1.0
505 ignore_cwise = params( la_linrx_cwise_i ) .EQ. 0.0
508 IF ( ref_type .EQ. 0 .OR. n_err_bnds .EQ. 0 )
THEN
510 ELSE IF ( ignore_cwise )
THEN
516 rcequ = lsame( equed,
'Y' )
520 IF ( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
THEN
522 ELSE IF( .NOT.rcequ .AND. .NOT.lsame( equed,
'N' ) )
THEN
524 ELSE IF( n.LT.0 )
THEN
526 ELSE IF( nrhs.LT.0 )
THEN
528 ELSE IF( lda.LT.max( 1, n ) )
THEN
530 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
532 ELSE IF( ldb.LT.max( 1, n ) )
THEN
534 ELSE IF( ldx.LT.max( 1, n ) )
THEN
538 CALL xerbla(
'SSYRFSX', -info )
544 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
548 IF ( n_err_bnds .GE. 1 )
THEN
549 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
550 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
552 IF ( n_err_bnds .GE. 2 )
THEN
553 err_bnds_norm( j, la_linrx_err_i ) = 0.0
554 err_bnds_comp( j, la_linrx_err_i ) = 0.0
556 IF ( n_err_bnds .GE. 3 )
THEN
557 err_bnds_norm( j, la_linrx_rcond_i ) = 1.0
558 err_bnds_comp( j, la_linrx_rcond_i ) = 1.0
569 IF ( n_err_bnds .GE. 1 )
THEN
570 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
571 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
573 IF ( n_err_bnds .GE. 2 )
THEN
574 err_bnds_norm( j, la_linrx_err_i ) = 1.0
575 err_bnds_comp( j, la_linrx_err_i ) = 1.0
577 IF ( n_err_bnds .GE. 3 )
THEN
578 err_bnds_norm( j, la_linrx_rcond_i ) = 0.0
579 err_bnds_comp( j, la_linrx_rcond_i ) = 0.0
587 anorm = slansy( norm, uplo, n, a, lda, work )
588 CALL ssycon( uplo, n, af, ldaf, ipiv, anorm, rcond, work,
593 IF ( ref_type .NE. 0 )
THEN
595 prec_type = ilaprec(
'D' )
598 $ nrhs, a, lda, af, ldaf, ipiv, rcequ, s, b,
599 $ ldb, x, ldx, berr, n_norms, err_bnds_norm, err_bnds_comp,
600 $ work( n+1 ), work( 1 ), work( 2*n+1 ), work( 1 ), rcond,
601 $ ithresh, rthresh, unstable_thresh, ignore_cwise,
605 err_lbnd = max( 10.0, sqrt( real( n ) ) )*slamch(
'Epsilon' )
606 IF (n_err_bnds .GE. 1 .AND. n_norms .GE. 1)
THEN
611 rcond_tmp = sla_syrcond( uplo, n, a, lda, af, ldaf, ipiv,
612 $ -1, s, info, work, iwork )
614 rcond_tmp = sla_syrcond( uplo, n, a, lda, af, ldaf, ipiv,
615 $ 0, s, info, work, iwork )
621 IF (n_err_bnds .GE. la_linrx_err_i
622 $ .AND. err_bnds_norm( j, la_linrx_err_i ) .GT. 1.0)
623 $ err_bnds_norm( j, la_linrx_err_i ) = 1.0
627 IF ( rcond_tmp .LT. illrcond_thresh )
THEN
628 err_bnds_norm( j, la_linrx_err_i ) = 1.0
629 err_bnds_norm( j, la_linrx_trust_i ) = 0.0
630 IF ( info .LE. n ) info = n + j
631 ELSE IF (err_bnds_norm( j, la_linrx_err_i ) .LT. err_lbnd)
633 err_bnds_norm( j, la_linrx_err_i ) = err_lbnd
634 err_bnds_norm( j, la_linrx_trust_i ) = 1.0
639 IF (n_err_bnds .GE. la_linrx_rcond_i)
THEN
640 err_bnds_norm( j, la_linrx_rcond_i ) = rcond_tmp
645 IF ( n_err_bnds .GE. 1 .AND. n_norms .GE. 2 )
THEN
655 cwise_wrong = sqrt( slamch(
'Epsilon' ) )
657 IF ( err_bnds_comp( j, la_linrx_err_i ) .LT. cwise_wrong )
659 rcond_tmp = sla_syrcond( uplo, n, a, lda, af, ldaf, ipiv,
660 $ 1, x(1,j), info, work, iwork )
667 IF ( n_err_bnds .GE. la_linrx_err_i
668 $ .AND. err_bnds_comp( j, la_linrx_err_i ) .GT. 1.0 )
669 $ err_bnds_comp( j, la_linrx_err_i ) = 1.0
673 IF ( rcond_tmp .LT. illrcond_thresh )
THEN
674 err_bnds_comp( j, la_linrx_err_i ) = 1.0
675 err_bnds_comp( j, la_linrx_trust_i ) = 0.0
676 IF ( .NOT. ignore_cwise
677 $ .AND. info.LT.n + j ) info = n + j
678 ELSE IF ( err_bnds_comp( j, la_linrx_err_i )
679 $ .LT. err_lbnd )
THEN
680 err_bnds_comp( j, la_linrx_err_i ) = err_lbnd
681 err_bnds_comp( j, la_linrx_trust_i ) = 1.0
686 IF ( n_err_bnds .GE. la_linrx_rcond_i )
THEN
687 err_bnds_comp( j, la_linrx_rcond_i ) = rcond_tmp
subroutine xerbla(srname, info)
subroutine ssycon(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)
SSYCON
subroutine ssyrfsx(uplo, equed, n, nrhs, a, lda, af, ldaf, ipiv, s, b, ldb, x, ldx, rcond, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
SSYRFSX
integer function ilaprec(prec)
ILAPREC
real function sla_syrcond(uplo, n, a, lda, af, ldaf, ipiv, cmode, c, info, work, iwork)
SLA_SYRCOND estimates the Skeel condition number for a symmetric indefinite matrix.
subroutine sla_syrfsx_extended(prec_type, uplo, n, nrhs, a, lda, af, ldaf, 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_SYRFSX_EXTENDED improves the computed solution to a system of linear equations for symmetric inde...
real function slamch(cmach)
SLAMCH
real function slansy(norm, uplo, n, a, lda, work)
SLANSY returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
logical function lsame(ca, cb)
LSAME