397 SUBROUTINE zherfsx( UPLO, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV,
398 $ S, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS,
399 $ ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS,
400 $ WORK, RWORK, INFO )
407 CHARACTER UPLO, EQUED
408 INTEGER INFO, LDA, LDAF, LDB, LDX, N, NRHS, NPARAMS,
410 DOUBLE PRECISION RCOND
414 COMPLEX*16 A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
415 $ X( LDX, * ), WORK( * )
416 DOUBLE PRECISION S( * ), PARAMS( * ), BERR( * ), RWORK( * ),
417 $ err_bnds_norm( nrhs, * ),
418 $ err_bnds_comp( nrhs, * )
423 DOUBLE PRECISION ZERO, ONE
424 PARAMETER ( ZERO = 0.0d+0, one = 1.0d+0 )
425 DOUBLE PRECISION ITREF_DEFAULT, ITHRESH_DEFAULT
426 DOUBLE PRECISION COMPONENTWISE_DEFAULT, RTHRESH_DEFAULT
427 DOUBLE PRECISION DZTHRESH_DEFAULT
428 parameter( itref_default = 1.0d+0 )
429 parameter( ithresh_default = 10.0d+0 )
430 parameter( componentwise_default = 1.0d+0 )
431 parameter( rthresh_default = 0.5d+0 )
432 parameter( dzthresh_default = 0.25d+0 )
433 INTEGER LA_LINRX_ITREF_I, LA_LINRX_ITHRESH_I,
435 parameter( la_linrx_itref_i = 1,
436 $ la_linrx_ithresh_i = 2 )
437 parameter( la_linrx_cwise_i = 3 )
438 INTEGER LA_LINRX_TRUST_I, LA_LINRX_ERR_I,
440 parameter( la_linrx_trust_i = 1, la_linrx_err_i = 2 )
441 parameter( la_linrx_rcond_i = 3 )
446 INTEGER J, PREC_TYPE, REF_TYPE
448 DOUBLE PRECISION ANORM, RCOND_TMP
449 DOUBLE PRECISION ILLRCOND_THRESH, ERR_LBND, CWISE_WRONG
452 DOUBLE PRECISION RTHRESH, UNSTABLE_THRESH
458 INTRINSIC max, sqrt, transfer
463 DOUBLE PRECISION DLAMCH, ZLANHE, ZLA_HERCOND_X, ZLA_HERCOND_C
472 ref_type = int( itref_default )
473 IF ( nparams .GE. la_linrx_itref_i )
THEN
474 IF ( params( la_linrx_itref_i ) .LT. 0.0d+0 )
THEN
475 params( la_linrx_itref_i ) = itref_default
477 ref_type = params( la_linrx_itref_i )
483 illrcond_thresh = dble( n ) * dlamch(
'Epsilon' )
484 ithresh = int( ithresh_default )
485 rthresh = rthresh_default
486 unstable_thresh = dzthresh_default
487 ignore_cwise = componentwise_default .EQ. 0.0d+0
489 IF ( nparams.GE.la_linrx_ithresh_i )
THEN
490 IF ( params( la_linrx_ithresh_i ).LT.0.0d+0 )
THEN
491 params( la_linrx_ithresh_i ) = ithresh
493 ithresh = int( params( la_linrx_ithresh_i ) )
496 IF ( nparams.GE.la_linrx_cwise_i )
THEN
497 IF ( params(la_linrx_cwise_i ).LT.0.0d+0 )
THEN
498 IF ( ignore_cwise )
THEN
499 params( la_linrx_cwise_i ) = 0.0d+0
501 params( la_linrx_cwise_i ) = 1.0d+0
504 ignore_cwise = params( la_linrx_cwise_i ) .EQ. 0.0d+0
507 IF ( ref_type .EQ. 0 .OR. n_err_bnds .EQ. 0 )
THEN
509 ELSE IF ( ignore_cwise )
THEN
515 rcequ = lsame( equed,
'Y' )
519 IF (.NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
THEN
521 ELSE IF( .NOT.rcequ .AND. .NOT.lsame( equed,
'N' ) )
THEN
523 ELSE IF( n.LT.0 )
THEN
525 ELSE IF( nrhs.LT.0 )
THEN
527 ELSE IF( lda.LT.max( 1, n ) )
THEN
529 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
531 ELSE IF( ldb.LT.max( 1, n ) )
THEN
533 ELSE IF( ldx.LT.max( 1, n ) )
THEN
537 CALL xerbla(
'ZHERFSX', -info )
543 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
547 IF ( n_err_bnds .GE. 1 )
THEN
548 err_bnds_norm( j, la_linrx_trust_i ) = 1.0d+0
549 err_bnds_comp( j, la_linrx_trust_i ) = 1.0d+0
551 IF ( n_err_bnds .GE. 2 )
THEN
552 err_bnds_norm( j, la_linrx_err_i ) = 0.0d+0
553 err_bnds_comp( j, la_linrx_err_i ) = 0.0d+0
555 IF ( n_err_bnds .GE. 3 )
THEN
556 err_bnds_norm( j, la_linrx_rcond_i ) = 1.0d+0
557 err_bnds_comp( j, la_linrx_rcond_i ) = 1.0d+0
568 IF ( n_err_bnds .GE. 1 )
THEN
569 err_bnds_norm( j, la_linrx_trust_i ) = 1.0d+0
570 err_bnds_comp( j, la_linrx_trust_i ) = 1.0d+0
572 IF ( n_err_bnds .GE. 2 )
THEN
573 err_bnds_norm( j, la_linrx_err_i ) = 1.0d+0
574 err_bnds_comp( j, la_linrx_err_i ) = 1.0d+0
576 IF ( n_err_bnds .GE. 3 )
THEN
577 err_bnds_norm( j, la_linrx_rcond_i ) = 0.0d+0
578 err_bnds_comp( j, la_linrx_rcond_i ) = 0.0d+0
586 anorm = zlanhe( norm, uplo, n, a, lda, rwork )
587 CALL zhecon( uplo, n, af, ldaf, ipiv, anorm, rcond, work,
592 IF ( ref_type .NE. 0 )
THEN
594 prec_type = ilaprec(
'E' )
597 $ nrhs, a, lda, af, ldaf, ipiv, rcequ, s, b,
598 $ ldb, x, ldx, berr, n_norms, err_bnds_norm, err_bnds_comp,
599 $ work, rwork, work(n+1),
600 $ transfer(rwork(1:2*n), (/ (zero, zero) /), n), rcond,
601 $ ithresh, rthresh, unstable_thresh, ignore_cwise,
605 err_lbnd = max( 10.0d+0, sqrt( dble( n ) ) ) * dlamch(
'Epsilon' )
606 IF ( n_err_bnds .GE. 1 .AND. n_norms .GE. 1 )
THEN
611 rcond_tmp = zla_hercond_c( uplo, n, a, lda, af, ldaf, ipiv,
612 $ s, .true., info, work, rwork )
614 rcond_tmp = zla_hercond_c( uplo, n, a, lda, af, ldaf, ipiv,
615 $ s, .false., info, work, rwork )
621 IF ( n_err_bnds .GE. la_linrx_err_i
622 $ .AND. err_bnds_norm( j, la_linrx_err_i ) .GT. 1.0d+0 )
623 $ err_bnds_norm( j, la_linrx_err_i ) = 1.0d+0
627 IF (rcond_tmp .LT. illrcond_thresh)
THEN
628 err_bnds_norm( j, la_linrx_err_i ) = 1.0d+0
629 err_bnds_norm( j, la_linrx_trust_i ) = 0.0d+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.0d+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( dlamch(
'Epsilon' ) )
657 IF ( err_bnds_comp( j, la_linrx_err_i ) .LT. cwise_wrong )
659 rcond_tmp = zla_hercond_x( uplo, n, a, lda, af, ldaf,
660 $ ipiv, x( 1, j ), info, work, rwork )
667 IF ( n_err_bnds .GE. la_linrx_err_i
668 $ .AND. err_bnds_comp( j, la_linrx_err_i ) .GT. 1.0d+0 )
669 $ err_bnds_comp( j, la_linrx_err_i ) = 1.0d+0
673 IF ( rcond_tmp .LT. illrcond_thresh )
THEN
674 err_bnds_comp( j, la_linrx_err_i ) = 1.0d+0
675 err_bnds_comp( j, la_linrx_trust_i ) = 0.0d+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.0d+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 zhecon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)
ZHECON
subroutine zherfsx(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, rwork, info)
ZHERFSX
integer function ilaprec(prec)
ILAPREC
double precision function zla_hercond_x(uplo, n, a, lda, af, ldaf, ipiv, x, info, work, rwork)
ZLA_HERCOND_X computes the infinity norm condition number of op(A)*diag(x) for Hermitian indefinite m...
double precision function zla_hercond_c(uplo, n, a, lda, af, ldaf, ipiv, c, capply, info, work, rwork)
ZLA_HERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for Hermitian indefin...
subroutine zla_herfsx_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)
ZLA_HERFSX_EXTENDED improves the computed solution to a system of linear equations for Hermitian inde...
double precision function dlamch(cmach)
DLAMCH
double precision function zlanhe(norm, uplo, n, a, lda, work)
ZLANHE returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
logical function lsame(ca, cb)
LSAME