Diff for /rpl/lapack/blas/ztrmm.f between versions 1.7 and 1.8

version 1.7, 2011/07/22 07:38:03 version 1.8, 2011/11/21 20:37:09
Line 1 Line 1
       SUBROUTINE ZTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)  *> \brief \b ZTRMM
 *     .. Scalar Arguments ..  
       DOUBLE COMPLEX ALPHA  
       INTEGER LDA,LDB,M,N  
       CHARACTER DIAG,SIDE,TRANSA,UPLO  
 *     ..  
 *     .. Array Arguments ..  
       DOUBLE COMPLEX A(LDA,*),B(LDB,*)  
 *     ..  
 *  
 *  Purpose  
 *  =======  
 *  
 *  ZTRMM  performs one of the matrix-matrix operations  
 *  *
 *     B := alpha*op( A )*B,   or   B := alpha*B*op( A )  *  =========== DOCUMENTATION ===========
 *  *
 *  where  alpha  is a scalar,  B  is an m by n matrix,  A  is a unit, or  * Online html documentation available at 
 *  non-unit,  upper or lower triangular matrix  and  op( A )  is one  of  *            http://www.netlib.org/lapack/explore-html/ 
 *  *
 *     op( A ) = A   or   op( A ) = A**T   or   op( A ) = A**H.  *  Definition:
   *  ===========
   *
   *       SUBROUTINE ZTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
   * 
   *       .. Scalar Arguments ..
   *       COMPLEX*16 ALPHA
   *       INTEGER LDA,LDB,M,N
   *       CHARACTER DIAG,SIDE,TRANSA,UPLO
   *       ..
   *       .. Array Arguments ..
   *       COMPLEX*16 A(LDA,*),B(LDB,*)
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> ZTRMM  performs one of the matrix-matrix operations
   *>
   *>    B := alpha*op( A )*B,   or   B := alpha*B*op( A )
   *>
   *> where  alpha  is a scalar,  B  is an m by n matrix,  A  is a unit, or
   *> non-unit,  upper or lower triangular matrix  and  op( A )  is one  of
   *>
   *>    op( A ) = A   or   op( A ) = A**T   or   op( A ) = A**H.
   *> \endverbatim
 *  *
 *  Arguments  *  Arguments:
 *  ==========  *  ==========
 *  *
 *  SIDE   - CHARACTER*1.  *> \param[in] SIDE
 *           On entry,  SIDE specifies whether  op( A ) multiplies B from  *> \verbatim
 *           the left or right as follows:  *>          SIDE is CHARACTER*1
 *  *>           On entry,  SIDE specifies whether  op( A ) multiplies B from
 *              SIDE = 'L' or 'l'   B := alpha*op( A )*B.  *>           the left or right as follows:
 *  *>
 *              SIDE = 'R' or 'r'   B := alpha*B*op( A ).  *>              SIDE = 'L' or 'l'   B := alpha*op( A )*B.
 *  *>
 *           Unchanged on exit.  *>              SIDE = 'R' or 'r'   B := alpha*B*op( A ).
 *  *> \endverbatim
 *  UPLO   - CHARACTER*1.  *>
 *           On entry, UPLO specifies whether the matrix A is an upper or  *> \param[in] UPLO
 *           lower triangular matrix as follows:  *> \verbatim
 *  *>          UPLO is CHARACTER*1
 *              UPLO = 'U' or 'u'   A is an upper triangular matrix.  *>           On entry, UPLO specifies whether the matrix A is an upper or
 *  *>           lower triangular matrix as follows:
 *              UPLO = 'L' or 'l'   A is a lower triangular matrix.  *>
 *  *>              UPLO = 'U' or 'u'   A is an upper triangular matrix.
 *           Unchanged on exit.  *>
 *  *>              UPLO = 'L' or 'l'   A is a lower triangular matrix.
 *  TRANSA - CHARACTER*1.  *> \endverbatim
 *           On entry, TRANSA specifies the form of op( A ) to be used in  *>
 *           the matrix multiplication as follows:  *> \param[in] TRANSA
 *  *> \verbatim
 *              TRANSA = 'N' or 'n'   op( A ) = A.  *>          TRANSA is CHARACTER*1
 *  *>           On entry, TRANSA specifies the form of op( A ) to be used in
 *              TRANSA = 'T' or 't'   op( A ) = A**T.  *>           the matrix multiplication as follows:
 *  *>
 *              TRANSA = 'C' or 'c'   op( A ) = A**H.  *>              TRANSA = 'N' or 'n'   op( A ) = A.
 *  *>
 *           Unchanged on exit.  *>              TRANSA = 'T' or 't'   op( A ) = A**T.
 *  *>
 *  DIAG   - CHARACTER*1.  *>              TRANSA = 'C' or 'c'   op( A ) = A**H.
 *           On entry, DIAG specifies whether or not A is unit triangular  *> \endverbatim
 *           as follows:  *>
 *  *> \param[in] DIAG
 *              DIAG = 'U' or 'u'   A is assumed to be unit triangular.  *> \verbatim
 *  *>          DIAG is CHARACTER*1
 *              DIAG = 'N' or 'n'   A is not assumed to be unit  *>           On entry, DIAG specifies whether or not A is unit triangular
 *                                  triangular.  *>           as follows:
 *  *>
 *           Unchanged on exit.  *>              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
 *  *>
 *  M      - INTEGER.  *>              DIAG = 'N' or 'n'   A is not assumed to be unit
 *           On entry, M specifies the number of rows of B. M must be at  *>                                  triangular.
 *           least zero.  *> \endverbatim
 *           Unchanged on exit.  *>
 *  *> \param[in] M
 *  N      - INTEGER.  *> \verbatim
 *           On entry, N specifies the number of columns of B.  N must be  *>          M is INTEGER
 *           at least zero.  *>           On entry, M specifies the number of rows of B. M must be at
 *           Unchanged on exit.  *>           least zero.
 *  *> \endverbatim
 *  ALPHA  - COMPLEX*16      .  *>
 *           On entry,  ALPHA specifies the scalar  alpha. When  alpha is  *> \param[in] N
 *           zero then  A is not referenced and  B need not be set before  *> \verbatim
 *           entry.  *>          N is INTEGER
 *           Unchanged on exit.  *>           On entry, N specifies the number of columns of B.  N must be
 *  *>           at least zero.
 *  A      - COMPLEX*16       array of DIMENSION ( LDA, k ), where k is m  *> \endverbatim
 *           when  SIDE = 'L' or 'l'  and is  n  when  SIDE = 'R' or 'r'.  *>
 *           Before entry  with  UPLO = 'U' or 'u',  the  leading  k by k  *> \param[in] ALPHA
 *           upper triangular part of the array  A must contain the upper  *> \verbatim
 *           triangular matrix  and the strictly lower triangular part of  *>          ALPHA is COMPLEX*16
 *           A is not referenced.  *>           On entry,  ALPHA specifies the scalar  alpha. When  alpha is
 *           Before entry  with  UPLO = 'L' or 'l',  the  leading  k by k  *>           zero then  A is not referenced and  B need not be set before
 *           lower triangular part of the array  A must contain the lower  *>           entry.
 *           triangular matrix  and the strictly upper triangular part of  *> \endverbatim
 *           A is not referenced.  *>
 *           Note that when  DIAG = 'U' or 'u',  the diagonal elements of  *> \param[in] A
 *           A  are not referenced either,  but are assumed to be  unity.  *> \verbatim
 *           Unchanged on exit.  *>          A is COMPLEX*16 array of DIMENSION ( LDA, k ), where k is m
 *  *>           when  SIDE = 'L' or 'l'  and is  n  when  SIDE = 'R' or 'r'.
 *  LDA    - INTEGER.  *>           Before entry  with  UPLO = 'U' or 'u',  the  leading  k by k
 *           On entry, LDA specifies the first dimension of A as declared  *>           upper triangular part of the array  A must contain the upper
 *           in the calling (sub) program.  When  SIDE = 'L' or 'l'  then  *>           triangular matrix  and the strictly lower triangular part of
 *           LDA  must be at least  max( 1, m ),  when  SIDE = 'R' or 'r'  *>           A is not referenced.
 *           then LDA must be at least max( 1, n ).  *>           Before entry  with  UPLO = 'L' or 'l',  the  leading  k by k
 *           Unchanged on exit.  *>           lower triangular part of the array  A must contain the lower
 *  *>           triangular matrix  and the strictly upper triangular part of
 *  B      - COMPLEX*16       array of DIMENSION ( LDB, n ).  *>           A is not referenced.
 *           Before entry,  the leading  m by n part of the array  B must  *>           Note that when  DIAG = 'U' or 'u',  the diagonal elements of
 *           contain the matrix  B,  and  on exit  is overwritten  by the  *>           A  are not referenced either,  but are assumed to be  unity.
 *           transformed matrix.  *> \endverbatim
 *  *>
 *  LDB    - INTEGER.  *> \param[in] LDA
 *           On entry, LDB specifies the first dimension of B as declared  *> \verbatim
 *           in  the  calling  (sub)  program.   LDB  must  be  at  least  *>          LDA is INTEGER
 *           max( 1, m ).  *>           On entry, LDA specifies the first dimension of A as declared
 *           Unchanged on exit.  *>           in the calling (sub) program.  When  SIDE = 'L' or 'l'  then
 *  *>           LDA  must be at least  max( 1, m ),  when  SIDE = 'R' or 'r'
 *  Further Details  *>           then LDA must be at least max( 1, n ).
 *  ===============  *> \endverbatim
   *>
   *> \param[in] B
   *> \verbatim
   *>          B is (input/output) COMPLEX*16 array of DIMENSION ( LDB, n ).
   *>           Before entry,  the leading  m by n part of the array  B must
   *>           contain the matrix  B,  and  on exit  is overwritten  by the
   *>           transformed matrix.
   *> \endverbatim
   *>
   *> \param[in] LDB
   *> \verbatim
   *>          LDB is INTEGER
   *>           On entry, LDB specifies the first dimension of B as declared
   *>           in  the  calling  (sub)  program.   LDB  must  be  at  least
   *>           max( 1, m ).
   *> \endverbatim
   *
   *  Authors:
   *  ========
   *
   *> \author Univ. of Tennessee 
   *> \author Univ. of California Berkeley 
   *> \author Univ. of Colorado Denver 
   *> \author NAG Ltd. 
   *
   *> \date November 2011
   *
   *> \ingroup complex16_blas_level3
   *
   *> \par Further Details:
   *  =====================
   *>
   *> \verbatim
   *>
   *>  Level 3 Blas routine.
   *>
   *>  -- Written on 8-February-1989.
   *>     Jack Dongarra, Argonne National Laboratory.
   *>     Iain Duff, AERE Harwell.
   *>     Jeremy Du Croz, Numerical Algorithms Group Ltd.
   *>     Sven Hammarling, Numerical Algorithms Group Ltd.
   *> \endverbatim
   *>
   *  =====================================================================
         SUBROUTINE ZTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
 *  *
 *  Level 3 Blas routine.  *  -- Reference BLAS level3 routine (version 3.4.0) --
   *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --
   *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
   *     November 2011
 *  *
 *  -- Written on 8-February-1989.  *     .. Scalar Arguments ..
 *     Jack Dongarra, Argonne National Laboratory.        COMPLEX*16 ALPHA
 *     Iain Duff, AERE Harwell.        INTEGER LDA,LDB,M,N
 *     Jeremy Du Croz, Numerical Algorithms Group Ltd.        CHARACTER DIAG,SIDE,TRANSA,UPLO
 *     Sven Hammarling, Numerical Algorithms Group Ltd.  *     ..
   *     .. Array Arguments ..
         COMPLEX*16 A(LDA,*),B(LDB,*)
   *     ..
 *  *
 *  =====================================================================  *  =====================================================================
 *  *
Line 138 Line 204
       INTRINSIC DCONJG,MAX        INTRINSIC DCONJG,MAX
 *     ..  *     ..
 *     .. Local Scalars ..  *     .. Local Scalars ..
       DOUBLE COMPLEX TEMP        COMPLEX*16 TEMP
       INTEGER I,INFO,J,K,NROWA        INTEGER I,INFO,J,K,NROWA
       LOGICAL LSIDE,NOCONJ,NOUNIT,UPPER        LOGICAL LSIDE,NOCONJ,NOUNIT,UPPER
 *     ..  *     ..
 *     .. Parameters ..  *     .. Parameters ..
       DOUBLE COMPLEX ONE        COMPLEX*16 ONE
       PARAMETER (ONE= (1.0D+0,0.0D+0))        PARAMETER (ONE= (1.0D+0,0.0D+0))
       DOUBLE COMPLEX ZERO        COMPLEX*16 ZERO
       PARAMETER (ZERO= (0.0D+0,0.0D+0))        PARAMETER (ZERO= (0.0D+0,0.0D+0))
 *     ..  *     ..
 *  *

Removed from v.1.7  
changed lines
  Added in v.1.8


CVSweb interface <joel.bertrand@systella.fr>