Skip to content

Commit

Permalink
skip "singularity" check in sytrf_aa tester
Browse files Browse the repository at this point in the history
  • Loading branch information
Ichitaro Yamazaki committed Jun 11, 2017
1 parent 3ba9cdf commit 99acde8
Show file tree
Hide file tree
Showing 6 changed files with 229 additions and 210 deletions.
79 changes: 41 additions & 38 deletions TESTING/LIN/cchkhe_aa.f
Original file line number Diff line number Diff line change
Expand Up @@ -434,22 +434,22 @@ SUBROUTINE CCHKHE_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Adjust the expected value of INFO to account for
* pivoting.
*
IF( IZERO.GT.0 ) THEN
J = 1
K = IZERO
100 CONTINUE
IF( J.EQ.K ) THEN
K = IWORK( J )
ELSE IF( IWORK( J ).EQ.K ) THEN
K = J
END IF
IF( J.LT.K ) THEN
J = J + 1
GO TO 100
END IF
ELSE
c IF( IZERO.GT.0 ) THEN
c J = 1
c K = IZERO
c 100 CONTINUE
c IF( J.EQ.K ) THEN
c K = IWORK( J )
c ELSE IF( IWORK( J ).EQ.K ) THEN
c K = J
c END IF
c IF( J.LT.K ) THEN
c J = J + 1
c GO TO 100
c END IF
c ELSE
K = 0
END IF
c END IF
*
* Check error code from CHETRF and handle error.
*
Expand Down Expand Up @@ -512,30 +512,33 @@ SUBROUTINE CCHKHE_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Check error code from CHETRS and handle error.
*
IF( INFO.NE.0 ) THEN
CALL ALAERH( PATH, 'CHETRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
*
CALL CLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA )
*
* Compute the residual for the solution
*
CALL CPOT02( UPLO, N, NRHS, A, LDA, X, LDA, WORK,
$ LDA, RWORK, RESULT( 2 ) )
*
* Print information about the tests that did not pass
* the threshold.
*
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
IF( IZERO.EQ.0 ) THEN
CALL ALAERH( PATH, 'CHETRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
120 CONTINUE
ELSE
CALL CLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA
$ )
*
* Compute the residual for the solution
*
CALL CPOT02( UPLO, N, NRHS, A, LDA, X, LDA,
$ WORK, LDA, RWORK, RESULT( 2 ) )
*
* Print information about the tests that did not pass
* the threshold.
*
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
END IF
120 CONTINUE
END IF
NRUN = NRUN + 1
*
* End do for each value of NRHS in NSVAL.
Expand Down
73 changes: 38 additions & 35 deletions TESTING/LIN/cchksy_aa.f
Original file line number Diff line number Diff line change
Expand Up @@ -435,22 +435,22 @@ SUBROUTINE CCHKSY_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Adjust the expected value of INFO to account for
* pivoting.
*
IF( IZERO.GT.0 ) THEN
J = 1
K = IZERO
100 CONTINUE
IF( J.EQ.K ) THEN
K = IWORK( J )
ELSE IF( IWORK( J ).EQ.K ) THEN
K = J
END IF
IF( J.LT.K ) THEN
J = J + 1
GO TO 100
END IF
ELSE
c IF( IZERO.GT.0 ) THEN
c J = 1
c K = IZERO
c 100 CONTINUE
c IF( J.EQ.K ) THEN
c K = IWORK( J )
c ELSE IF( IWORK( J ).EQ.K ) THEN
c K = J
c END IF
c IF( J.LT.K ) THEN
c J = J + 1
c GO TO 100
c END IF
c ELSE
K = 0
END IF
c END IF
*
* Check error code from CSYTRF and handle error.
*
Expand Down Expand Up @@ -514,31 +514,34 @@ SUBROUTINE CCHKSY_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Check error code from CSYTRS and handle error.
*
IF( INFO.NE.0 ) THEN
CALL ALAERH( PATH, 'CSYTRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
*
CALL CLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA )
IF( IZERO.EQ.0 ) THEN
CALL ALAERH( PATH, 'CSYTRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
ELSE
CALL CLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA
$ )
*
* Compute the residual for the solution
* Compute the residual for the solution
*
CALL CSYT02( UPLO, N, NRHS, A, LDA, X, LDA, WORK,
$ LDA, RWORK, RESULT( 2 ) )
CALL CSYT02( UPLO, N, NRHS, A, LDA, X, LDA,
$ WORK, LDA, RWORK, RESULT( 2 ) )
*
*
* Print information about the tests that did not pass
* the threshold.
* Print information about the tests that did not pass
* the threshold.
*
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
END IF
120 CONTINUE
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
END IF
120 CONTINUE
END IF
NRUN = NRUN + 1
*
* End do for each value of NRHS in NSVAL.
Expand Down
73 changes: 38 additions & 35 deletions TESTING/LIN/dchksy_aa.f
Original file line number Diff line number Diff line change
Expand Up @@ -432,22 +432,22 @@ SUBROUTINE DCHKSY_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Adjust the expected value of INFO to account for
* pivoting.
*
IF( IZERO.GT.0 ) THEN
J = 1
K = IZERO
100 CONTINUE
IF( J.EQ.K ) THEN
K = IWORK( J )
ELSE IF( IWORK( J ).EQ.K ) THEN
K = J
END IF
IF( J.LT.K ) THEN
J = J + 1
GO TO 100
END IF
ELSE
c IF( IZERO.GT.0 ) THEN
c J = 1
c K = IZERO
c 100 CONTINUE
c IF( J.EQ.K ) THEN
c K = IWORK( J )
c ELSE IF( IWORK( J ).EQ.K ) THEN
c K = J
c END IF
c IF( J.LT.K ) THEN
c J = J + 1
c GO TO 100
c END IF
c ELSE
K = 0
END IF
c END IF
*
* Check error code from DSYTRF and handle error.
*
Expand Down Expand Up @@ -511,31 +511,34 @@ SUBROUTINE DCHKSY_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Check error code from DSYTRS and handle error.
*
IF( INFO.NE.0 ) THEN
CALL ALAERH( PATH, 'DSYTRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
*
CALL DLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA )
IF( IZERO.EQ.0 ) THEN
CALL ALAERH( PATH, 'DSYTRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
ELSE
CALL DLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA
$ )
*
* Compute the residual for the solution
* Compute the residual for the solution
*
CALL DPOT02( UPLO, N, NRHS, A, LDA, X, LDA, WORK,
$ LDA, RWORK, RESULT( 2 ) )
CALL DPOT02( UPLO, N, NRHS, A, LDA, X, LDA,
$ WORK, LDA, RWORK, RESULT( 2 ) )
*
*
* Print information about the tests that did not pass
* the threshold.
* Print information about the tests that did not pass
* the threshold.
*
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
END IF
120 CONTINUE
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
END IF
120 CONTINUE
END IF
NRUN = NRUN + 1
*
* End do for each value of NRHS in NSVAL.
Expand Down
69 changes: 36 additions & 33 deletions TESTING/LIN/schksy_aa.f
Original file line number Diff line number Diff line change
Expand Up @@ -433,22 +433,22 @@ SUBROUTINE SCHKSY_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Adjust the expected value of INFO to account for
* pivoting.
*
IF( IZERO.GT.0 ) THEN
J = 1
K = IZERO
100 CONTINUE
IF( J.EQ.K ) THEN
K = IWORK( J )
ELSE IF( IWORK( J ).EQ.K ) THEN
K = J
END IF
IF( J.LT.K ) THEN
J = J + 1
GO TO 100
END IF
ELSE
c IF( IZERO.GT.0 ) THEN
c J = 1
c K = IZERO
c 100 CONTINUE
c IF( J.EQ.K ) THEN
c K = IWORK( J )
c ELSE IF( IWORK( J ).EQ.K ) THEN
c K = J
c END IF
c IF( J.LT.K ) THEN
c J = J + 1
c GO TO 100
c END IF
c ELSE
K = 0
END IF
c END IF
*
* Check error code from SSYTRF and handle error.
*
Expand Down Expand Up @@ -512,31 +512,34 @@ SUBROUTINE SCHKSY_AA( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
* Check error code from SSYTRS and handle error.
*
IF( INFO.NE.0 ) THEN
CALL ALAERH( PATH, 'SSYTRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
*
CALL SLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA )
IF( IZERO.EQ.0 ) THEN
CALL ALAERH( PATH, 'SSYTRS_AA', INFO, 0,
$ UPLO, N, N, -1, -1, NRHS, IMAT,
$ NFAIL, NERRS, NOUT )
END IF
ELSE
CALL SLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA
$ )
*
* Compute the residual for the solution
* Compute the residual for the solution
*
CALL SPOT02( UPLO, N, NRHS, A, LDA, X, LDA, WORK,
$ LDA, RWORK, RESULT( 2 ) )
CALL SPOT02( UPLO, N, NRHS, A, LDA, X, LDA,
$ WORK, LDA, RWORK, RESULT( 2 ) )
*
*
* Print information about the tests that did not pass
* the threshold.
*
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
END IF
120 CONTINUE
DO 120 K = 2, 2
IF( RESULT( K ).GE.THRESH ) THEN
IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
$ CALL ALAHD( NOUT, PATH )
WRITE( NOUT, FMT = 9998 )UPLO, N, NRHS,
$ IMAT, K, RESULT( K )
NFAIL = NFAIL + 1
END IF
120 CONTINUE
END IF
NRUN = NRUN + 1
*
* End do for each value of NRHS in NSVAL.
Expand Down
Loading

0 comments on commit 99acde8

Please sign in to comment.