fixed comments in LAPACK testing routines (s,d,c,z)lavsy.f, (s,d,c,z)lavsy_rook.f...
authorigor175 <igor175@8a072113-8704-0410-8d35-dd094bca7971>
Thu, 18 Apr 2013 00:39:57 +0000 (00:39 +0000)
committerigor175 <igor175@8a072113-8704-0410-8d35-dd094bca7971>
Thu, 18 Apr 2013 00:39:57 +0000 (00:39 +0000)
12 files changed:
TESTING/LIN/clavhe.f
TESTING/LIN/clavhe_rook.f
TESTING/LIN/clavsy.f
TESTING/LIN/clavsy_rook.f
TESTING/LIN/dlavsy.f
TESTING/LIN/dlavsy_rook.f
TESTING/LIN/slavsy.f
TESTING/LIN/slavsy_rook.f
TESTING/LIN/zlavhe.f
TESTING/LIN/zlavhe_rook.f
TESTING/LIN/zlavsy.f
TESTING/LIN/zlavsy_rook.f

index d4bd8beca93e7fcf6767e86a8c1067b472a29129..b236a5fe1b2db889d08d21d2915b3c0f71000d82 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 CLAVHE( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                          LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX            A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
 *> \verbatim
 *>
-*>    CLAVHE  performs one of the matrix-vector operations
-*>       x := A*x  or  x := A^H*x,
-*>    where x is an N element vector and  A is one of the factors
-*>    from the symmetric factorization computed by CHETRF.
-*>    CHETRF produces a factorization of the form
-*>         U * D * U^H     or     L * D * L^H,
-*>    where U (or L) is a product of permutation and unit upper (lower)
-*>    triangular matrices, U^H (or L^H) is the conjugate transpose of
-*>    U (or L), and D is Hermitian and block diagonal with 1 x 1 and
-*>    2 x 2 diagonal blocks.  The multipliers for the transformations
-*>    and the upper or lower triangular parts of the diagonal blocks
-*>    are stored in the leading upper or lower triangle of the 2-D
-*>    array A.
+*> CLAVHE performs one of the matrix-vector operations
+*>    x := A*x  or  x := A^H*x,
+*> where x is an N element vector and  A is one of the factors
+*> from the block U*D*U' or L*D*L' factorization computed by CHETRF.
 *>
-*>    If TRANS = 'N' or 'n', CLAVHE multiplies either by U or U * D
-*>    (or L or L * D).
-*>    If TRANS = 'C' or 'c', CLAVHE multiplies either by U^H or D * U^H
-*>    (or L^H or D * L^H ).
+*> If TRANS = 'N', multiplies by U  or U * D  (or L  or L * D)
+*> If TRANS = 'C', multiplies by U' or D * U' (or L' or D * L')
 *> \endverbatim
 *
 *  Arguments:
 *  ==========
 *
+*> \param[in] UPLO
+*> \verbatim
+*>          UPLO is CHARACTER*1
+*>          Specifies whether the factor stored in A is upper or lower
+*>          triangular.
+*>          = 'U':  Upper triangular
+*>          = 'L':  Lower triangular
+*> \endverbatim
+*>
+*> \param[in] TRANS
+*> \verbatim
+*>          TRANS is CHARACTER*1
+*>          Specifies the operation to be performed:
+*>          = 'N':  x := A*x
+*>          = 'C':   x := A^H*x
+*> \endverbatim
+*>
+*> \param[in] DIAG
+*> \verbatim
+*>          DIAG is CHARACTER*1
+*>          Specifies whether or not the diagonal blocks are unit
+*>          matrices.  If the diagonal blocks are assumed to be unit,
+*>          then A = U or A = L, otherwise A = U*D or A = L*D.
+*>          = 'U':  Diagonal blocks are assumed to be unit matrices.
+*>          = 'N':  Diagonal blocks are assumed to be non-unit matrices.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*>          N is INTEGER
+*>          The number of rows and columns of the matrix A.  N >= 0.
+*> \endverbatim
+*>
+*> \param[in] NRHS
 *> \verbatim
-*>  UPLO   - CHARACTER*1
-*>           On entry, UPLO specifies whether the triangular matrix
-*>           stored in A is upper or lower triangular.
-*>              UPLO = 'U' or 'u'   The matrix is upper triangular.
-*>              UPLO = 'L' or 'l'   The matrix is lower triangular.
-*>           Unchanged on exit.
+*>          NRHS is INTEGER
+*>          The number of right hand sides, i.e., the number of vectors
+*>          x to be multiplied by A.  NRHS >= 0.
+*> \endverbatim
 *>
-*>  TRANS  - CHARACTER*1
-*>           On entry, TRANS specifies the operation to be performed as
-*>           follows:
-*>              TRANS = 'N' or 'n'   x := A*x.
-*>              TRANS = 'C' or 'c'   x := A^H*x.
-*>           Unchanged on exit.
+*> \param[in] A
+*> \verbatim
+*>          A is COMPLEX array, dimension (LDA,N)
+*>          The block diagonal matrix D and the multipliers used to
+*>          obtain the factor U or L as computed by CHETRF_ROOK.
+*>          Stored as a 2-D triangular matrix.
+*> \endverbatim
 *>
-*>  DIAG   - CHARACTER*1
-*>           On entry, DIAG specifies whether the diagonal blocks are
-*>           assumed to be unit matrices:
-*>              DIAG = 'U' or 'u'   Diagonal blocks are unit matrices.
-*>              DIAG = 'N' or 'n'   Diagonal blocks are non-unit.
-*>           Unchanged on exit.
+*> \param[in] LDA
+*> \verbatim
+*>          LDA is INTEGER
+*>          The leading dimension of the array A.  LDA >= max(1,N).
+*> \endverbatim
 *>
-*>  N      - INTEGER
-*>           On entry, N specifies the order of the matrix A.
-*>           N must be at least zero.
-*>           Unchanged on exit.
+*> \param[in] IPIV
+*> \verbatim
+*>          IPIV is INTEGER array, dimension (N)
+*>          Details of the interchanges and the block structure of D,
+*>          as determined by CHETRF.
 *>
-*>  NRHS   - INTEGER
-*>           On entry, NRHS specifies the number of right hand sides,
-*>           i.e., the number of vectors x to be multiplied by A.
-*>           NRHS must be at least zero.
-*>           Unchanged on exit.
+*>          If UPLO = 'U':
+*>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
+*>               were interchanged and D(k,k) is a 1-by-1 diagonal block.
+*>               (If IPIV( k ) = k, no interchange was done).
 *>
-*>  A      - COMPLEX array, dimension( LDA, N )
-*>           On entry, A contains a block diagonal matrix and the
-*>           multipliers of the transformations used to obtain it,
-*>           stored as a 2-D triangular matrix.
-*>           Unchanged on exit.
+*>               If IPIV(k) = IPIV(k-1) < 0, then rows and
+*>               columns k-1 and -IPIV(k) were interchanged,
+*>               D(k-1:k,k-1:k) is a 2-by-2 diagonal block.
 *>
-*>  LDA    - INTEGER
-*>           On entry, LDA specifies the first dimension of A as declared
-*>           in the calling ( sub ) program. LDA must be at least
-*>           max( 1, N ).
-*>           Unchanged on exit.
+*>          If UPLO = 'L':
+*>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
+*>               were interchanged and D(k,k) is a 1-by-1 diagonal block.
+*>               (If IPIV( k ) = k, no interchange was done).
 *>
-*>  IPIV   - INTEGER array, dimension( N )
-*>           On entry, IPIV contains the vector of pivot indices as
-*>           determined by CSYTRF or CHETRF.
-*>           If IPIV( K ) = K, no interchange was done.
-*>           If IPIV( K ) <> K but IPIV( K ) > 0, then row K was inter-
-*>           changed with row IPIV( K ) and a 1 x 1 pivot block was used.
-*>           If IPIV( K ) < 0 and UPLO = 'U', then row K-1 was exchanged
-*>           with row | IPIV( K ) | and a 2 x 2 pivot block was used.
-*>           If IPIV( K ) < 0 and UPLO = 'L', then row K+1 was exchanged
-*>           with row | IPIV( K ) | and a 2 x 2 pivot block was used.
+*>               If IPIV(k) = IPIV(k+1) < 0, then rows and
+*>               columns k+1 and -IPIV(k) were interchanged,
+*>               D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
+*> \endverbatim
 *>
-*>  B      - COMPLEX array, dimension( LDB, NRHS )
-*>           On entry, B contains NRHS vectors of length N.
-*>           On exit, B is overwritten with the product A * B.
+*> \param[in,out] B
+*> \verbatim
+*>          B is COMPLEX array, dimension (LDB,NRHS)
+*>          On entry, B contains NRHS vectors of length N.
+*>          On exit, B is overwritten with the product A * B.
+*> \endverbatim
 *>
-*>  LDB    - INTEGER
-*>           On entry, LDB contains the leading dimension of B as
-*>           declared in the calling program.  LDB must be at least
-*>           max( 1, N ).
-*>           Unchanged on exit.
+*> \param[in] LDB
+*> \verbatim
+*>          LDB is INTEGER
+*>          The leading dimension of the array B.  LDB >= max(1,N).
+*> \endverbatim
 *>
-*>  INFO   - INTEGER
-*>           INFO is the error flag.
-*>           On exit, a value of 0 indicates a successful exit.
-*>           A negative value, say -K, indicates that the K-th argument
-*>           has an illegal value.
+*> \param[out] INFO
+*> \verbatim
+*>          INFO is INTEGER
+*>          = 0: successful exit
+*>          < 0: if INFO = -k, the k-th argument had an illegal value
 *> \endverbatim
 *
 *  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
 *
index 4946a5e22ee42e49a415090d19553553ae6582db..49cbb4438933b1caac55a18003e31e6875b0f846 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 CLAVHE_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                               LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX            A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
 *> \verbatim
 *>
-*> CLAVHE_ROOK  performs one of the matrix-vector operations
+*> CLAVHE_ROOK performs one of the matrix-vector operations
 *>    x := A*x  or  x := A^H*x,
 *> where x is an N element vector and  A is one of the factors
-*> from the Hermitian factorization computed by CHETRF_ROOK.
-*>
-*> CHETRF_ROOK produces a factorization of the form
-*>      U * D * U^H     or     L * D * L^H,
-*> where U (or L) is a product of permutation and unit upper (lower)
-*> triangular matrices, U^H (or L^H) is the conjugate transpose of
-*> U (or L), and D is Hermitian and block diagonal with 1 x 1 and
-*> 2 x 2 diagonal blocks.  The multipliers for the transformations
-*> and the upper or lower triangular parts of the diagonal blocks
-*> are stored in the leading upper or lower triangle of the 2-D
-*> array A.
+*> from the block U*D*U' or L*D*L' factorization computed by CHETRF_ROOK.
 *>
 *> If TRANS = 'N', multiplies by U  or U * D  (or L  or L * D)
-*> If TRANS = 'T', multiplies by U' or D * U' (or L' or D * L')
 *> If TRANS = 'C', multiplies by U' or D * U' (or L' or D * L')
 *> \endverbatim
 *
@@ -63,7 +52,6 @@
 *>          TRANS is CHARACTER*1
 *>          Specifies the operation to be performed:
 *>          = 'N':  x := A*x
-*>          = 'T':   x := A^H*x
 *>          = 'C':   x := A^H*x
 *> \endverbatim
 *>
@@ -95,6 +83,7 @@
 *>          A is COMPLEX array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by CHETRF_ROOK.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
 *  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
 *
index 50153d50dcbb31919945f96abb875390b4e0355e..82099cf5c0c904f6671aac8712bb0dd875daf51f 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 CLAVSY( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                          LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX            A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
 *> \verbatim
 *>
-*> CLAVSY_ROOK  performs one of the matrix-vector operations
+*> CLAVSY performs one of the matrix-vector operations
 *>    x := A*x  or  x := A'*x,
 *> where x is an N element vector and  A is one of the factors
-*> from the block U*D*U' or L*D*L' factorization computed by CSYTRF_ROOK.
+*> from the block U*D*U' or L*D*L' factorization computed by CSYTRF.
 *>
 *> If TRANS = 'N', multiplies by U  or U * D  (or L  or L * D)
 *> If TRANS = 'T', multiplies by U' or D * U' (or L' or D * L')
@@ -82,7 +82,8 @@
 *> \verbatim
 *>          A is COMPLEX array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
-*>          obtain the factor U or L as computed by CSYTRF_ROOK.
+*>          obtain the factor U or L as computed by CSYTRF.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
@@ -95,7 +96,7 @@
 *> \verbatim
 *>          IPIV is INTEGER array, dimension (N)
 *>          Details of the interchanges and the block structure of D,
-*>          as determined by CSYTRF_ROOK or CHETRF_ROOK.
+*>          as determined by CSYTRF.
 *>
 *>          If UPLO = 'U':
 *>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
 *  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
 *
index 265b2193a6f7fb6340b00e3300569207a853fad5..4a13ab1541b0a519725d1345715b65c3f04a176f 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 CLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
-*                          LDB, INFO )
-* 
+*                               LDB, INFO )
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX            A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
 *> \verbatim
 *>
-*> CLAVSY_ROOK  performs one of the matrix-vector operations
+*> CLAVSY_ROOK performs one of the matrix-vector operations
 *>    x := A*x  or  x := A'*x,
 *> where x is an N element vector and  A is one of the factors
 *> from the block U*D*U' or L*D*L' factorization computed by CSYTRF_ROOK.
@@ -83,6 +83,7 @@
 *>          A is COMPLEX array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by CSYTRF_ROOK.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
@@ -95,7 +96,7 @@
 *> \verbatim
 *>          IPIV is INTEGER array, dimension (N)
 *>          Details of the interchanges and the block structure of D,
-*>          as determined by CSYTRF_ROOK or CHETRF_ROOK.
+*>          as determined by CSYTRF_ROOK.
 *>
 *>          If UPLO = 'U':
 *>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
 *  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
 *
 *
 *  =====================================================================
       SUBROUTINE CLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV,
-     $                    B, LDB, INFO )
+     $                        B, LDB, INFO )
 *
 *  -- LAPACK test routine (version 3.4.0) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
index e869ac0a86e89e7d5f4545ad0007f7c286a8c50e..53898d439692210a3658008308c9439835c78e03 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 DLAVSY( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                          LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
@@ -19,7 +19,7 @@
 *       INTEGER            IPIV( * )
 *       DOUBLE PRECISION   A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
@@ -85,6 +85,7 @@
 *>          A is DOUBLE PRECISION array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by DSYTRF.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
 *  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
 *
index 4d233757ec028f4d611b7f98c7fbb3a1c4412e15..f8501a6bec2fcde86482f113f4555ba059d7de84 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 DLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
-*                          LDB, INFO )
-* 
+*                               LDB, INFO )
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
@@ -19,7 +19,7 @@
 *       INTEGER            IPIV( * )
 *       DOUBLE PRECISION   A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
@@ -85,6 +85,7 @@
 *>          A is DOUBLE PRECISION array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by DSYTRF_ROOK.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
 *  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
 *
 *
 *  =====================================================================
       SUBROUTINE DLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV,
-     $                    B, LDB, INFO )
+     $                        B, LDB, INFO )
 *
 *  -- LAPACK test routine (version 3.4.1) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
index 5f78afb826685a2fda645553092cf64f920bba53..5c978bb00b81edbb21f5f843c37d4e69b6cbf3c0 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 SLAVSY( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                          LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
@@ -19,7 +19,7 @@
 *       INTEGER            IPIV( * )
 *       REAL               A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
@@ -85,6 +85,7 @@
 *>          A is REAL array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by SSYTRF.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
 *  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
 *
index b4e3260a861b5f20de6a95cb32c532c4d21965b7..b5cb0cce91d3089d8782c5e0029ed9c55b3b9271 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 SLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
-*                          LDB, INFO )
-* 
+*                               LDB, INFO )
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
@@ -19,7 +19,7 @@
 *       INTEGER            IPIV( * )
 *       REAL               A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
@@ -85,6 +85,7 @@
 *>          A is REAL array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by SSYTRF_ROOK.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
 *  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
 *
 *
 *  =====================================================================
       SUBROUTINE SLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV,
-     $                    B, LDB, INFO )
+     $                        B, LDB, INFO )
 *
 *  -- LAPACK test routine (version 3.4.0) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
index fd0bedcb2322ee921cfa1f0f03902963479cbf55..4e4ad2f5b7fc826b943508faddb2b573f504d40c 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 ZLAVHE( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                          LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX*16         A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
 *> \verbatim
 *>
-*>    ZLAVHE  performs one of the matrix-vector operations
-*>       x := A*x  or  x := A^H*x,
-*>    where x is an N element vector and  A is one of the factors
-*>    from the symmetric factorization computed by ZHETRF.
-*>    ZHETRF produces a factorization of the form
-*>         U * D * U^H     or     L * D * L^H,
-*>    where U (or L) is a product of permutation and unit upper (lower)
-*>    triangular matrices, U^H (or L^H) is the conjugate transpose of
-*>    U (or L), and D is Hermitian and block diagonal with 1 x 1 and
-*>    2 x 2 diagonal blocks.  The multipliers for the transformations
-*>    and the upper or lower triangular parts of the diagonal blocks
-*>    are stored in the leading upper or lower triangle of the 2-D
-*>    array A.
+*> ZLAVHE performs one of the matrix-vector operations
+*>    x := A*x  or  x := A^H*x,
+*> where x is an N element vector and  A is one of the factors
+*> from the block U*D*U' or L*D*L' factorization computed by ZHETRF.
 *>
-*>    If TRANS = 'N' or 'n', ZLAVHE multiplies either by U or U * D
-*>    (or L or L * D).
-*>    If TRANS = 'C' or 'c', ZLAVHE multiplies either by U^H or D * U^H
-*>    (or L^H or D * L^H ).
+*> If TRANS = 'N', multiplies by U  or U * D  (or L  or L * D)
+*> If TRANS = 'C', multiplies by U' or D * U' (or L' or D * L')
 *> \endverbatim
 *
 *  Arguments:
 *  ==========
 *
+*> \param[in] UPLO
+*> \verbatim
+*>          UPLO is CHARACTER*1
+*>          Specifies whether the factor stored in A is upper or lower
+*>          triangular.
+*>          = 'U':  Upper triangular
+*>          = 'L':  Lower triangular
+*> \endverbatim
+*>
+*> \param[in] TRANS
+*> \verbatim
+*>          TRANS is CHARACTER*1
+*>          Specifies the operation to be performed:
+*>          = 'N':  x := A*x
+*>          = 'C':  x := A'*x
+*> \endverbatim
+*>
+*> \param[in] DIAG
+*> \verbatim
+*>          DIAG is CHARACTER*1
+*>          Specifies whether or not the diagonal blocks are unit
+*>          matrices.  If the diagonal blocks are assumed to be unit,
+*>          then A = U or A = L, otherwise A = U*D or A = L*D.
+*>          = 'U':  Diagonal blocks are assumed to be unit matrices.
+*>          = 'N':  Diagonal blocks are assumed to be non-unit matrices.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*>          N is INTEGER
+*>          The number of rows and columns of the matrix A.  N >= 0.
+*> \endverbatim
+*>
+*> \param[in] NRHS
 *> \verbatim
-*>  UPLO   - CHARACTER*1
-*>           On entry, UPLO specifies whether the triangular matrix
-*>           stored in A is upper or lower triangular.
-*>              UPLO = 'U' or 'u'   The matrix is upper triangular.
-*>              UPLO = 'L' or 'l'   The matrix is lower triangular.
-*>           Unchanged on exit.
+*>          NRHS is INTEGER
+*>          The number of right hand sides, i.e., the number of vectors
+*>          x to be multiplied by A.  NRHS >= 0.
+*> \endverbatim
 *>
-*>  TRANS  - CHARACTER*1
-*>           On entry, TRANS specifies the operation to be performed as
-*>           follows:
-*>              TRANS = 'N' or 'n'   x := A*x.
-*>              TRANS = 'C' or 'c'   x := A^H*x.
-*>           Unchanged on exit.
+*> \param[in] A
+*> \verbatim
+*>          A is COMPLEX*16 array, dimension (LDA,N)
+*>          The block diagonal matrix D and the multipliers used to
+*>          obtain the factor U or L as computed by ZHETRF.
+*>          Stored as a 2-D triangular matrix.
+*> \endverbatim
 *>
-*>  DIAG   - CHARACTER*1
-*>           On entry, DIAG specifies whether the diagonal blocks are
-*>           assumed to be unit matrices:
-*>              DIAG = 'U' or 'u'   Diagonal blocks are unit matrices.
-*>              DIAG = 'N' or 'n'   Diagonal blocks are non-unit.
-*>           Unchanged on exit.
+*> \param[in] LDA
+*> \verbatim
+*>          LDA is INTEGER
+*>          The leading dimension of the array A.  LDA >= max(1,N).
+*> \endverbatim
 *>
-*>  N      - INTEGER
-*>           On entry, N specifies the order of the matrix A.
-*>           N must be at least zero.
-*>           Unchanged on exit.
+*> \param[in] IPIV
+*> \verbatim
+*>          IPIV is INTEGER array, dimension (N)
+*>          Details of the interchanges and the block structure of D,
+*>          as determined by ZHETRF.
 *>
-*>  NRHS   - INTEGER
-*>           On entry, NRHS specifies the number of right hand sides,
-*>           i.e., the number of vectors x to be multiplied by A.
-*>           NRHS must be at least zero.
-*>           Unchanged on exit.
+*>          If UPLO = 'U':
+*>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
+*>               were interchanged and D(k,k) is a 1-by-1 diagonal block.
+*>               (If IPIV( k ) = k, no interchange was done).
 *>
-*>  A      - COMPLEX*16 array, dimension( LDA, N )
-*>           On entry, A contains a block diagonal matrix and the
-*>           multipliers of the transformations used to obtain it,
-*>           stored as a 2-D triangular matrix.
-*>           Unchanged on exit.
+*>               If IPIV(k) = IPIV(k-1) < 0, then rows and
+*>               columns k-1 and -IPIV(k) were interchanged,
+*>               D(k-1:k,k-1:k) is a 2-by-2 diagonal block.
 *>
-*>  LDA    - INTEGER
-*>           On entry, LDA specifies the first dimension of A as declared
-*>           in the calling ( sub ) program. LDA must be at least
-*>           max( 1, N ).
-*>           Unchanged on exit.
+*>          If UPLO = 'L':
+*>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
+*>               were interchanged and D(k,k) is a 1-by-1 diagonal block.
+*>               (If IPIV( k ) = k, no interchange was done).
 *>
-*>  IPIV   - INTEGER array, dimension( N )
-*>           On entry, IPIV contains the vector of pivot indices as
-*>           determined by ZSYTRF or ZHETRF.
-*>           If IPIV( K ) = K, no interchange was done.
-*>           If IPIV( K ) <> K but IPIV( K ) > 0, then row K was inter-
-*>           changed with row IPIV( K ) and a 1 x 1 pivot block was used.
-*>           If IPIV( K ) < 0 and UPLO = 'U', then row K-1 was exchanged
-*>           with row | IPIV( K ) | and a 2 x 2 pivot block was used.
-*>           If IPIV( K ) < 0 and UPLO = 'L', then row K+1 was exchanged
-*>           with row | IPIV( K ) | and a 2 x 2 pivot block was used.
+*>               If IPIV(k) = IPIV(k+1) < 0, then rows and
+*>               columns k+1 and -IPIV(k) were interchanged,
+*>               D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
+*> \endverbatim
 *>
-*>  B      - COMPLEX*16 array, dimension( LDB, NRHS )
-*>           On entry, B contains NRHS vectors of length N.
-*>           On exit, B is overwritten with the product A * B.
+*> \param[in,out] B
+*> \verbatim
+*>          B is COMPLEX*16 array, dimension (LDB,NRHS)
+*>          On entry, B contains NRHS vectors of length N.
+*>          On exit, B is overwritten with the product A * B.
+*> \endverbatim
 *>
-*>  LDB    - INTEGER
-*>           On entry, LDB contains the leading dimension of B as
-*>           declared in the calling program.  LDB must be at least
-*>           max( 1, N ).
-*>           Unchanged on exit.
+*> \param[in] LDB
+*> \verbatim
+*>          LDB is INTEGER
+*>          The leading dimension of the array B.  LDB >= max(1,N).
+*> \endverbatim
 *>
-*>  INFO   - INTEGER
-*>           INFO is the error flag.
-*>           On exit, a value of 0 indicates a successful exit.
-*>           A negative value, say -K, indicates that the K-th argument
-*>           has an illegal value.
+*> \param[out] INFO
+*> \verbatim
+*>          INFO is INTEGER
+*>          = 0: successful exit
+*>          < 0: if INFO = -k, the k-th argument had an illegal value
 *> \endverbatim
 *
 *  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
 *
index 8470591a849f726659358f12b02203c4c5ce83f0..6bac48ccfff999d890bcc31d10f7c908bbee353d 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 ZLAVHE_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                               LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX*16         A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
-*> \verbatim
-*>
-*> ZLAVHE_ROOK  performs one of the matrix-vector operations
+*> ZLAVHE_ROOK performs one of the matrix-vector operations
 *>    x := A*x  or  x := A^H*x,
 *> where x is an N element vector and  A is one of the factors
-*> from the Hermitian factorization computed by CHETRF_ROOK.
-*>
-*> ZHETRF_ROOK produces a factorization of the form
-*>      U * D * U^H     or     L * D * L^H,
-*> where U (or L) is a product of permutation and unit upper (lower)
-*> triangular matrices, U^H (or L^H) is the conjugate transpose of
-*> U (or L), and D is Hermitian and block diagonal with 1 x 1 and
-*> 2 x 2 diagonal blocks.  The multipliers for the transformations
-*> and the upper or lower triangular parts of the diagonal blocks
-*> are stored in the leading upper or lower triangle of the 2-D
-*> array A.
+*> from the block U*D*U' or L*D*L' factorization computed by ZHETRF_ROOK.
 *>
 *> If TRANS = 'N', multiplies by U  or U * D  (or L  or L * D)
-*> If TRANS = 'T', multiplies by U' or D * U' (or L' or D * L')
 *> If TRANS = 'C', multiplies by U' or D * U' (or L' or D * L')
-*> \endverbatim
 *
 *  Arguments:
 *  ==========
@@ -63,7 +49,7 @@
 *>          TRANS is CHARACTER*1
 *>          Specifies the operation to be performed:
 *>          = 'N':  x := A*x
-*>          = 'T':   x := A^H*x
+*>          = 'C':   x := A^H*x
 *> \endverbatim
 *>
 *> \param[in] DIAG
@@ -94,6 +80,7 @@
 *>          A is COMPLEX*16 array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by ZHETRF_ROOK.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
 *  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 ..
       COMPLEX*16         CONE
-      PARAMETER          ( CONE = ( 1.0E+0, 0.0E+0 ) )
+      PARAMETER          ( CONE = ( 1.0D+0, 0.0D+0 ) )
 *     ..
 *     .. Local Scalars ..
       LOGICAL            NOUNIT
index df638a95be522d13e20ac0880fb96198377cc85a..6c2fd65df4d419f22f1c41e8b44e4307c6b8cd70 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 ZLAVSY( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
 *                          LDB, INFO )
-* 
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX*16         A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
 *> \verbatim
 *>
-*> ZLAVSY_ROOK  performs one of the matrix-vector operations
+*> ZLAVSY performs one of the matrix-vector operations
 *>    x := A*x  or  x := A'*x,
 *> where x is an N element vector and  A is one of the factors
-*> from the block U*D*U' or L*D*L' factorization computed by ZSYTRF_ROOK.
+*> from the block U*D*U' or L*D*L' factorization computed by ZSYTRF.
 *>
 *> If TRANS = 'N', multiplies by U  or U * D  (or L  or L * D)
 *> If TRANS = 'T', multiplies by U' or D * U' (or L' or D * L')
@@ -82,7 +82,8 @@
 *> \verbatim
 *>          A is COMPLEX*16 array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
-*>          obtain the factor U or L as computed by ZSYTRF_ROOK.
+*>          obtain the factor U or L as computed by ZSYTRF.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
@@ -95,7 +96,7 @@
 *> \verbatim
 *>          IPIV is INTEGER array, dimension (N)
 *>          Details of the interchanges and the block structure of D,
-*>          as determined by ZSYTRF_ROOK or ZHETRF_ROOK.
+*>          as determined by ZSYTRF.
 *>
 *>          If UPLO = 'U':
 *>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
 *  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
 *
index 3744726da6523c398111757bbbf4afd9e0d4a4cd..d91118dd4d1adfa11305216868a74fcda82817f9 100644 (file)
@@ -2,15 +2,15 @@
 *
 *  =========== 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 ZLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
-*                          LDB, INFO )
-* 
+*                               LDB, INFO )
+*
 *       .. Scalar Arguments ..
 *       CHARACTER          DIAG, TRANS, UPLO
 *       INTEGER            INFO, LDA, LDB, N, NRHS
 *       INTEGER            IPIV( * )
 *       COMPLEX*16         A( LDA, * ), B( LDB, * )
 *       ..
-*  
+*
 *
 *> \par Purpose:
 *  =============
 *>
 *> \verbatim
 *>
-*> ZLAVSY_ROOK  performs one of the matrix-vector operations
+*> ZLAVSY_ROOK performs one of the matrix-vector operations
 *>    x := A*x  or  x := A'*x,
 *> where x is an N element vector and  A is one of the factors
 *> from the block U*D*U' or L*D*L' factorization computed by ZSYTRF_ROOK.
@@ -83,6 +83,7 @@
 *>          A is COMPLEX*16 array, dimension (LDA,N)
 *>          The block diagonal matrix D and the multipliers used to
 *>          obtain the factor U or L as computed by ZSYTRF_ROOK.
+*>          Stored as a 2-D triangular matrix.
 *> \endverbatim
 *>
 *> \param[in] LDA
@@ -95,7 +96,7 @@
 *> \verbatim
 *>          IPIV is INTEGER array, dimension (N)
 *>          Details of the interchanges and the block structure of D,
-*>          as determined by ZSYTRF_ROOK or ZHETRF_ROOK.
+*>          as determined by ZSYTRF_ROOK.
 *>
 *>          If UPLO = 'U':
 *>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
 *  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
 *
 *
 *  =====================================================================
       SUBROUTINE ZLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV,
-     $                    B, LDB, INFO )
+     $                        B, LDB, INFO )
 *
 *  -- LAPACK test routine (version 3.4.0) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --