Contents


NAME

     strmm - perform one of the matrix-matrix operations    B  :=
     alpha*op( A )*B, or B := alpha*B*op( A )

SYNOPSIS

     SUBROUTINE STRMM(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B,
           LDB)

     CHARACTER * 1 SIDE, UPLO, TRANSA, DIAG
     INTEGER M, N, LDA, LDB
     REAL ALPHA
     REAL A(LDA,*), B(LDB,*)

     SUBROUTINE STRMM_64(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B,
           LDB)

     CHARACTER * 1 SIDE, UPLO, TRANSA, DIAG
     INTEGER*8 M, N, LDA, LDB
     REAL ALPHA
     REAL A(LDA,*), B(LDB,*)

  F95 INTERFACE
     SUBROUTINE TRMM(SIDE, UPLO, [TRANSA], DIAG, [M], [N], ALPHA, A, [LDA],
            B, [LDB])

     CHARACTER(LEN=1) :: SIDE, UPLO, TRANSA, DIAG
     INTEGER :: M, N, LDA, LDB
     REAL :: ALPHA
     REAL, DIMENSION(:,:) :: A, B

     SUBROUTINE TRMM_64(SIDE, UPLO, [TRANSA], DIAG, [M], [N], ALPHA, A,
            [LDA], B, [LDB])

     CHARACTER(LEN=1) :: SIDE, UPLO, TRANSA, DIAG
     INTEGER(8) :: M, N, LDA, LDB
     REAL :: ALPHA
     REAL, DIMENSION(:,:) :: A, B

  C INTERFACE
     #include <sunperf.h>

     void strmm(char side, char uplo, char transa, char diag, int
               m,  int  n,  float alpha, float *a, int lda, float
               *b, int ldb);

     void strmm_64(char side, char uplo, char transa, char  diag,
               long  m,  long n, float alpha, float *a, long lda,
               float *b, long ldb);

PURPOSE

     strmm 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'.

ARGUMENTS

     SIDE (input)
               On entry,  SIDE specifies whether  op( A )  multi-
               plies 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 (input)
               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 (input)
               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'.

               TRANSA = 'C' or 'c'   op( A ) = A'.

               Unchanged on exit.

               TRANSA is defaulted to 'N' for F95 INTERFACE.
     DIAG (input)
               On entry, DIAG specifies whether or not A is  unit
               triangular as follows:

               DIAG = 'U' or 'u'   A is assumed to be  unit  tri-
               angular.

               DIAG = 'N' or 'n'   A is not assumed  to  be  unit
               triangular.

               Unchanged on exit.

     M (input)
               On entry, M specifies the number of rows of  B.  M
               >= 0.  Unchanged on exit.

     N (input)
               On entry, N specifies the number of columns of  B.
               N >= 0.  Unchanged on exit.

     ALPHA (input)
               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 (input)
               REAL 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  lead-
               ing   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 refer-
               enced.

               Before entry  with  UPLO = 'L' or 'l',  the  lead-
               ing   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 refer-
               enced.

               Note that when  DIAG = 'U' or 'u',   the  diagonal
               elements  of A are not referenced either,  but are
               assumed to be one.  Unchanged on exit.

     LDA (input)
               On entry, LDA specifies the first dimension  of  A
               as  declared  in  the calling (sub) program.  When
               SIDE = 'L' or 'l'  then LDA >= max( 1, m  ),  when
               SIDE  =  'R'  or  'r'  then  LDA  >=  max( 1, n ).
               Unchanged on exit.

     B (input/output)
               REAL array of DIMENSION ( LDB, n ).  Before entry,
               the leading  m by n part of the array  B must con-
               tain the matrix  B,  and  on exit  is  overwritten
               by the transformed matrix.

     LDB (input)
               On entry, LDB specifies the first dimension  of  B
               as  declared  in   the   calling   (sub)  program.
               LDB >= max( 1, m ).  Unchanged on exit.