Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zgemm (3p)

Name

zgemm - matrix operations C := alpha*op( A )*op( B ) + beta*C

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                            zgemm(3P)



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


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       zgemm 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'   or   op(X) = conjg(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 ) = conjg( A' ).

                 Unchanged on exit.


       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 ) = conjg( B' ).

                 Unchanged on exit.


       M (input)
                 On entry,  M  specifies  the number  of rows  of the   matrix
                 op(  A )  and of the  matrix  C.  M >= 0.  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 >= 0.
                 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 >= 0.
                 Unchanged on exit.


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


       A (input)
                 COMPLEX*16 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), otherwise LDA >= max(1, K).   Unchanged  on
                 exit.


       B (input)
                 COMPLEX*16  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 ), otherwise  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)
                 COMPLEX*16  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.




                                  7 Nov 2015                         zgemm(3P)