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

version 1.7, 2011/07/22 07:38:02 version 1.8, 2011/11/21 20:37:08
Line 1 Line 1
   *> \brief \b DTRMM
   *
   *  =========== DOCUMENTATION ===========
   *
   * Online html documentation available at 
   *            http://www.netlib.org/lapack/explore-html/ 
   *
   *  Definition:
   *  ===========
   *
   *       SUBROUTINE DTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
   * 
   *       .. Scalar Arguments ..
   *       DOUBLE PRECISION ALPHA
   *       INTEGER LDA,LDB,M,N
   *       CHARACTER DIAG,SIDE,TRANSA,UPLO
   *       ..
   *       .. Array Arguments ..
   *       DOUBLE PRECISION A(LDA,*),B(LDB,*)
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> DTRMM  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.
   *> \endverbatim
   *
   *  Arguments:
   *  ==========
   *
   *> \param[in] SIDE
   *> \verbatim
   *>          SIDE is CHARACTER*1
   *>           On entry,  SIDE specifies whether  op( A ) multiplies B from
   *>           the left or right as follows:
   *>
   *>              SIDE = 'L' or 'l'   B := alpha*op( A )*B.
   *>
   *>              SIDE = 'R' or 'r'   B := alpha*B*op( A ).
   *> \endverbatim
   *>
   *> \param[in] UPLO
   *> \verbatim
   *>          UPLO is CHARACTER*1
   *>           On entry, UPLO specifies whether the matrix A is an upper or
   *>           lower triangular matrix as follows:
   *>
   *>              UPLO = 'U' or 'u'   A is an upper triangular matrix.
   *>
   *>              UPLO = 'L' or 'l'   A is a lower triangular matrix.
   *> \endverbatim
   *>
   *> \param[in] TRANSA
   *> \verbatim
   *>          TRANSA is CHARACTER*1
   *>           On entry, TRANSA specifies the form of op( A ) to be used in
   *>           the matrix multiplication as follows:
   *>
   *>              TRANSA = 'N' or 'n'   op( A ) = A.
   *>
   *>              TRANSA = 'T' or 't'   op( A ) = A**T.
   *>
   *>              TRANSA = 'C' or 'c'   op( A ) = A**T.
   *> \endverbatim
   *>
   *> \param[in] DIAG
   *> \verbatim
   *>          DIAG is CHARACTER*1
   *>           On entry, DIAG specifies whether or not A is unit triangular
   *>           as follows:
   *>
   *>              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
   *>
   *>              DIAG = 'N' or 'n'   A is not assumed to be unit
   *>                                  triangular.
   *> \endverbatim
   *>
   *> \param[in] M
   *> \verbatim
   *>          M is INTEGER
   *>           On entry, M specifies the number of rows of B. M must be at
   *>           least zero.
   *> \endverbatim
   *>
   *> \param[in] N
   *> \verbatim
   *>          N is INTEGER
   *>           On entry, N specifies the number of columns of B.  N must be
   *>           at least zero.
   *> \endverbatim
   *>
   *> \param[in] ALPHA
   *> \verbatim
   *>          ALPHA is DOUBLE PRECISION.
   *>           On entry,  ALPHA specifies the scalar  alpha. When  alpha is
   *>           zero then  A is not referenced and  B need not be set before
   *>           entry.
   *> \endverbatim
   *>
   *> \param[in] A
   *> \verbatim
   *>           A is DOUBLE PRECISION array of DIMENSION ( LDA, k ), where k is m
   *>           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
   *>           upper triangular part of the array  A must contain the upper
   *>           triangular matrix  and the strictly lower triangular part of
   *>           A is not referenced.
   *>           Before entry  with  UPLO = 'L' or 'l',  the  leading  k by k
   *>           lower triangular part of the array  A must contain the lower
   *>           triangular matrix  and the strictly upper triangular part of
   *>           A is not referenced.
   *>           Note that when  DIAG = 'U' or 'u',  the diagonal elements of
   *>           A  are not referenced either,  but are assumed to be  unity.
   *> \endverbatim
   *>
   *> \param[in] LDA
   *> \verbatim
   *>          LDA is INTEGER
   *>           On entry, LDA specifies the first dimension of A as declared
   *>           in the calling (sub) program.  When  SIDE = 'L' or 'l'  then
   *>           LDA  must be at least  max( 1, m ),  when  SIDE = 'R' or 'r'
   *>           then LDA must be at least max( 1, n ).
   *> \endverbatim
   *>
   *> \param[in,out] B
   *> \verbatim
   *>          B is DOUBLE PRECISION 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 double_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 DTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)        SUBROUTINE DTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
   *
   *  -- 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
   *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       DOUBLE PRECISION ALPHA        DOUBLE PRECISION ALPHA
       INTEGER LDA,LDB,M,N        INTEGER LDA,LDB,M,N
Line 8 Line 191
       DOUBLE PRECISION A(LDA,*),B(LDB,*)        DOUBLE PRECISION A(LDA,*),B(LDB,*)
 *     ..  *     ..
 *  *
 *  Purpose  
 *  =======  
 *  
 *  DTRMM  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.  
 *  
 *  Arguments  
 *  ==========  
 *  
 *  SIDE   - CHARACTER*1.  
 *           On entry,  SIDE specifies whether  op( A ) multiplies B from  
 *           the left or right as follows:  
 *  
 *              SIDE = 'L' or 'l'   B := alpha*op( A )*B.  
 *  
 *              SIDE = 'R' or 'r'   B := alpha*B*op( A ).  
 *  
 *           Unchanged on exit.  
 *  
 *  UPLO   - CHARACTER*1.  
 *           On entry, UPLO specifies whether the matrix A is an upper or  
 *           lower triangular matrix as follows:  
 *  
 *              UPLO = 'U' or 'u'   A is an upper triangular matrix.  
 *  
 *              UPLO = 'L' or 'l'   A is a lower triangular matrix.  
 *  
 *           Unchanged on exit.  
 *  
 *  TRANSA - CHARACTER*1.  
 *           On entry, TRANSA specifies the form of op( A ) to be used in  
 *           the matrix multiplication as follows:  
 *  
 *              TRANSA = 'N' or 'n'   op( A ) = A.  
 *  
 *              TRANSA = 'T' or 't'   op( A ) = A**T.  
 *  
 *              TRANSA = 'C' or 'c'   op( A ) = A**T.  
 *  
 *           Unchanged on exit.  
 *  
 *  DIAG   - CHARACTER*1.  
 *           On entry, DIAG specifies whether or not A is unit triangular  
 *           as follows:  
 *  
 *              DIAG = 'U' or 'u'   A is assumed to be unit triangular.  
 *  
 *              DIAG = 'N' or 'n'   A is not assumed to be unit  
 *                                  triangular.  
 *  
 *           Unchanged on exit.  
 *  
 *  M      - INTEGER.  
 *           On entry, M specifies the number of rows of B. M must be at  
 *           least zero.  
 *           Unchanged on exit.  
 *  
 *  N      - INTEGER.  
 *           On entry, N specifies the number of columns of B.  N must be  
 *           at least zero.  
 *           Unchanged on exit.  
 *  
 *  ALPHA  - DOUBLE PRECISION.  
 *           On entry,  ALPHA specifies the scalar  alpha. When  alpha is  
 *           zero then  A is not referenced and  B need not be set before  
 *           entry.  
 *           Unchanged on exit.  
 *  
 *  A      - DOUBLE PRECISION array of DIMENSION ( LDA, k ), where k is m  
 *           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  
 *           upper triangular part of the array  A must contain the upper  
 *           triangular matrix  and the strictly lower triangular part of  
 *           A is not referenced.  
 *           Before entry  with  UPLO = 'L' or 'l',  the  leading  k by k  
 *           lower triangular part of the array  A must contain the lower  
 *           triangular matrix  and the strictly upper triangular part of  
 *           A is not referenced.  
 *           Note that when  DIAG = 'U' or 'u',  the diagonal elements of  
 *           A  are not referenced either,  but are assumed to be  unity.  
 *           Unchanged on exit.  
 *  
 *  LDA    - INTEGER.  
 *           On entry, LDA specifies the first dimension of A as declared  
 *           in the calling (sub) program.  When  SIDE = 'L' or 'l'  then  
 *           LDA  must be at least  max( 1, m ),  when  SIDE = 'R' or 'r'  
 *           then LDA must be at least max( 1, n ).  
 *           Unchanged on exit.  
 *  
 *  B      - DOUBLE PRECISION 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.  
 *  
 *  LDB    - 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 ).  
 *           Unchanged on exit.  
 *  
 *  Further Details  
 *  ===============  
 *  
 *  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.  
 *  
 *  =====================================================================  *  =====================================================================
 *  *
 *     .. External Functions ..  *     .. External Functions ..

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


CVSweb interface <joel.bertrand@systella.fr>