*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE CDRVHE( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
* A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
* NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
* $ WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is COMPLEX array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date November 2011
*
*
* Initialize constants and the random number seed.
*
- PATH( 1: 1 ) = 'C'
+ PATH( 1: 1 ) = 'Complex precision'
PATH( 2: 3 ) = 'HE'
NRUN = 0
NFAIL = 0
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE CDRVHE_ROOK( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
* NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK,
* IWORK, NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
* $ WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is COMPLEX array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date April 2013
*
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE CDRVSY( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
* A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
* NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
* $ WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is COMPLEX array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date November 2011
*
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE CDRVSY_ROOK( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
* NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK,
* IWORK, NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
* $ WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX array, dimension
-*> (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date November 2011
*
*
IF( IMAT.NE.NTYPES ) THEN
*
-* Begin generate the test matrix A.
+* Begin generate the test matrix A.
*
-* Set up parameters with CLATB4 for the matrix generator
-* based on the type of matrix to be generated.
+* Set up parameters with CLATB4 for the matrix generator
+* based on the type of matrix to be generated.
*
CALL CLATB4( MATPATH, IMAT, N, N, TYPE, KL, KU, ANORM,
$ MODE, CNDNUM, DIST )
*
-* Generate a matrix with CLATMS.
+* Generate a matrix with CLATMS.
*
SRNAMT = 'CLATMS'
CALL CLATMS( N, N, DIST, ISEED, TYPE, RWORK, MODE,
$ CNDNUM, ANORM, KL, KU, UPLO, A, LDA,
$ WORK, INFO )
*
-* Check error code from DLATMS and handle error.
+* Check error code from CLATMS and handle error.
*
IF( INFO.NE.0 ) THEN
CALL ALAERH( PATH, 'CLATMS', INFO, 0, UPLO, N, N,
ELSE
IZERO = 0
END IF
+*
+* End generate the test matrix A.
+*
ELSE
*
* IMAT = NTYPES: Use a special block diagonal matrix to
FACT = FACTS( IFACT )
*
* Compute the condition number for comparison with
-* the value returned by ZSYSVX_ROOK.
+* the value returned by CSYSVX_ROOK.
*
IF( ZEROT ) THEN
IF( IFACT.EQ.1 )
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE DDRVSY( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
* A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
* NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* DOUBLE PRECISION A( * ), AFAC( * ), AINV( * ), B( * ),
* $ RWORK( * ), WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is DOUBLE PRECISION array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is DOUBLE PRECISION array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date November 2011
*
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE DDRVSY_ROOK( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
* $ NMAX, A, AFAC, AINV, B, X, XACT, WORK,
* $ RWORK, IWORK, NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* DOUBLE PRECISION A( * ), AFAC( * ), AINV( * ), B( * ),
* $ RWORK( * ), WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is DOUBLE PRECISION array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is DOUBLE PRECISION array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date April 2012
*
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE SDRVSY( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
* A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
* NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* REAL A( * ), AFAC( * ), AINV( * ), B( * ),
* $ RWORK( * ), WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is REAL array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is REAL array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date November 2011
*
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE SDRVSY_ROOK( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
* $ NMAX, A, AFAC, AINV, B, X, XACT, WORK,
* $ RWORK, IWORK, NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* REAL A( * ), AFAC( * ), AINV( * ), B( * ),
* $ RWORK( * ), WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date April 2012
*
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE ZDRVHE( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
* A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
* NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* COMPLEX*16 A( * ), AFAC( * ), AINV( * ), B( * ),
* $ WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX*16 array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is COMPLEX*16 array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date November 2011
*
*
* Initialize constants and the random number seed.
*
- PATH( 1: 1 ) = 'Z'
+ PATH( 1: 1 ) = 'Zomplex precision'
PATH( 2: 3 ) = 'HE'
NRUN = 0
NFAIL = 0
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE ZDRVHE_ROOK( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
* NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK,
* IWORK, NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* COMPLEX*16 A( * ), AFAC( * ), AINV( * ), B( * ),
* $ WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX*16 array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is COMPLEX*16 array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date April 2013
*
*
* .. Parameters ..
DOUBLE PRECISION ONE, ZERO
- PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
+ PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
INTEGER NTYPES, NTESTS
PARAMETER ( NTYPES = 10, NTESTS = 3 )
INTEGER NFACT
*
* =========== DOCUMENTATION ===========
*
-* Online html documentation available at
-* http://www.netlib.org/lapack/explore-html/
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
*
* Definition:
* ===========
* SUBROUTINE ZDRVSY( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
* A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
* NOUT )
-*
+*
* .. Scalar Arguments ..
* LOGICAL TSTERR
* INTEGER NMAX, NN, NOUT, NRHS
* COMPLEX*16 A( * ), AFAC( * ), AINV( * ), B( * ),
* $ WORK( * ), X( * ), XACT( * )
* ..
-*
+*
*
*> \par Purpose:
* =============
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX*16 array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is COMPLEX*16 array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK
* Authors:
* ========
*
-*> \author Univ. of Tennessee
-*> \author Univ. of California Berkeley
-*> \author Univ. of Colorado Denver
-*> \author NAG Ltd.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
*> \date November 2011
*
*>
*> \param[out] WORK
*> \verbatim
-*> WORK is COMPLEX*16 array, dimension
-*> (NMAX*max(2,NRHS))
+*> WORK is COMPLEX*16 array, dimension (NMAX*max(2,NRHS))
*> \endverbatim
*>
*> \param[out] RWORK