Contents


NAME

     dgemm - perform one of the matrix-matrix operations    C  :=
     alpha*op( A )*op( B ) + beta*C

SYNOPSIS

     SUBROUTINE DGEMM(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB,
           BETA, C, LDC)

     CHARACTER * 1 TRANSA, TRANSB
     INTEGER M, N, K, LDA, LDB, LDC
     DOUBLE PRECISION ALPHA, BETA
     DOUBLE PRECISION A(LDA,*), B(LDB,*), C(LDC,*)

     SUBROUTINE DGEMM_64(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB,
           BETA, C, LDC)

     CHARACTER * 1 TRANSA, TRANSB
     INTEGER*8 M, N, K, LDA, LDB, LDC
     DOUBLE PRECISION ALPHA, BETA
     DOUBLE PRECISION A(LDA,*), B(LDB,*), C(LDC,*)

  F95 INTERFACE
     SUBROUTINE GEMM([TRANSA], [TRANSB], [M], [N], [K], ALPHA, A, [LDA],
            B, [LDB], BETA, C, [LDC])

     CHARACTER(LEN=1) :: TRANSA, TRANSB
     INTEGER :: M, N, K, LDA, LDB, LDC
     REAL(8) :: ALPHA, BETA
     REAL(8), DIMENSION(:,:) :: A, B, C

     SUBROUTINE GEMM_64([TRANSA], [TRANSB], [M], [N], [K], ALPHA, A, [LDA],
            B, [LDB], BETA, C, [LDC])

     CHARACTER(LEN=1) :: TRANSA, TRANSB
     INTEGER(8) :: M, N, K, LDA, LDB, LDC
     REAL(8) :: ALPHA, BETA
     REAL(8), DIMENSION(:,:) :: A, B, C

  C INTERFACE
     #include <sunperf.h>

     void dgemm(char transa, char transb, int m, int  n,  int  k,
               double  alpha,  double *a, int lda, double *b, int
               ldb, double beta, double *c, int ldc);

     void dgemm_64(char transa, char transb, long m, long n, long
               k,  double  alpha, double *a, long lda, double *b,
               long ldb, double beta, double *c, long ldc);

PURPOSE

     dgemm performs one of  the  matrix-matrix  operations  C  :=
     alpha*op( A )*op( B ) + beta*C where  op( X ) is one of

        op( X ) = X   or   op( X ) = X',

     alpha and beta are scalars, and A, B  and  C  are  matrices,
     with  op(  A  ) an m by k matrix,  op( B )  a  k by n matrix
     and  C an m by n matrix.

ARGUMENTS

     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.

     TRANSB (input)
               On entry, TRANSB specifies the form of op( B )  to
               be used in the matrix multiplication as follows:

               TRANSB = 'N' or 'n',  op( B ) = B.

               TRANSB = 'T' or 't',  op( B ) = B'.

               TRANSB = 'C' or 'c',  op( B ) = B'.

               Unchanged on exit.

               TRANSB is defaulted to 'N' for F95 INTERFACE.

     M (input)
               On entry,  M  specifies  the number  of  rows   of
               the   matrix  op(  A  )  and of the  matrix  C.  M
               must  be at least  zero.  Unchanged on exit.
     N (input)
               On entry,  N  specifies the number  of columns  of
               the  matrix  op(  B ) and the number of columns of
               the matrix C. N must be at least zero.   Unchanged
               on exit.

     K (input)
               On entry,  K  specifies  the number of columns  of
               the  matrix  op( A ) and the number of rows of the
               matrix  op(  B  ).  K  must  be  at  least   zero.
               Unchanged on exit.

     ALPHA (input)
               On  entry,  ALPHA  specifies  the  scalar   alpha.
               Unchanged on exit.

     A (input)
               DOUBLE PRECISION array of DIMENSION ( LDA,  ka  ),
               where  ka is k  when  TRANSA = 'N' or 'n',  and is
               m  otherwise.  Before entry with  TRANSA = 'N'  or
               'n',   the  leading   m  by k part of the array  A
               must contain the matrix  A,  otherwise the leading
               k  by  m   part of the array  A  must contain  the
               matrix A.  Unchanged on exit.

     LDA (input)
               On entry, LDA specifies the first dimension  of  A
               as  declared  in  the  calling (sub) program. When
               TRANSA = 'N' or 'n' then LDA >= max( 1, m ),  oth-
               erwise  LDA >= max( 1, k ).  Unchanged on exit.

     B (input)
               DOUBLE PRECISION array of DIMENSION ( LDB,  kb  ),
               where  kb is n  when  TRANSB = 'N' or 'n',  and is
               k  otherwise.  Before entry with  TRANSB = 'N'  or
               'n',   the  leading   k  by n part of the array  B
               must contain the matrix  B,  otherwise the leading
               n  by  k   part of the array  B  must contain  the
               matrix B.  Unchanged on exit.

     LDB (input)
               On entry, LDB specifies the first dimension  of  B
               as  declared  in  the  calling (sub) program. When
               TRANSB = 'N' or 'n' then LDB >= max( 1, k ),  oth-
               erwise LDB >= max( 1, n ).  Unchanged on exit.
     BETA (input)
               On entry,  BETA  specifies the scalar  beta.  When
               BETA   is  supplied as zero then C need not be set
               on input.  Unchanged on exit.

     C (input/output)
               DOUBLE PRECISION array of DIMENSION (  LDC,  n  ).
               Before  entry,  the  leading   m by n  part of the
               array  C must contain the matrix  C,  except  when
               beta   is zero, in which case C need not be set on
               entry.  On exit, the array  C  is  overwritten  by
               the   m  by  n   matrix  ( alpha*op( A )*op( B ) +
               beta*C ).

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