Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zhemm (3p)

Name

zhemm - matrix operations C := alpha*A*B + beta*C or C := alpha*B*A + beta*C

Synopsis

SUBROUTINE ZHEMM(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB, BETA, C,
LDC)

CHARACTER*1 SIDE, UPLO
DOUBLE COMPLEX ALPHA, BETA
DOUBLE COMPLEX A(LDA,*), B(LDB,*), C(LDC,*)
INTEGER M, N, LDA, LDB, LDC

SUBROUTINE ZHEMM_64(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB, BETA, C,
LDC)

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




F95 INTERFACE
SUBROUTINE HEMM(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB,
BETA, C, LDC)

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

SUBROUTINE HEMM_64(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB,
BETA, C, LDC)

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




C INTERFACE
#include <sunperf.h>

void zhemm(char side, char uplo, int m, int  n,  doublecomplex  *alpha,
doublecomplex *a, int lda, doublecomplex *b, int ldb, double-
complex *beta, doublecomplex *c, int ldc);

void zhemm_64(char side, char  uplo,  long  m,  long  n,  doublecomplex
*alpha,  doublecomplex  *a,  long lda, doublecomplex *b, long
ldb, doublecomplex *beta, doublecomplex *c, long ldc);

Description

Oracle Solaris Studio Performance Library                            zhemm(3P)



NAME
       zhemm  -  perform  one of the matrix-matrix operations C := alpha*A*B +
       beta*C or C := alpha*B*A + beta*C


SYNOPSIS
       SUBROUTINE ZHEMM(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB, BETA, C,
             LDC)

       CHARACTER*1 SIDE, UPLO
       DOUBLE COMPLEX ALPHA, BETA
       DOUBLE COMPLEX A(LDA,*), B(LDB,*), C(LDC,*)
       INTEGER M, N, LDA, LDB, LDC

       SUBROUTINE ZHEMM_64(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB, BETA, C,
             LDC)

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




   F95 INTERFACE
       SUBROUTINE HEMM(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB,
              BETA, C, LDC)

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

       SUBROUTINE HEMM_64(SIDE, UPLO, M, N, ALPHA, A, LDA, B, LDB,
              BETA, C, LDC)

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




   C INTERFACE
       #include <sunperf.h>

       void zhemm(char side, char uplo, int m, int  n,  doublecomplex  *alpha,
                 doublecomplex *a, int lda, doublecomplex *b, int ldb, double-
                 complex *beta, doublecomplex *c, int ldc);

       void zhemm_64(char side, char  uplo,  long  m,  long  n,  doublecomplex
                 *alpha,  doublecomplex  *a,  long lda, doublecomplex *b, long
                 ldb, doublecomplex *beta, doublecomplex *c, long ldc);



PURPOSE
       zhemm performs one of the matrix-matrix operations  C  :=  alpha*A*B  +
       beta*C  or  C := alpha*B*A + beta*C where alpha and beta are scalars, A
       is an hermitian matrix and  B and C are m by n matrices.


ARGUMENTS
       SIDE (input)
                 On entry,  SIDE  specifies whether  the  hermitian matrix   A
                 appears on the  left or right  in the  operation as follows:

                 SIDE = 'L' or 'l'   C := alpha*A*B + beta*C,

                 SIDE = 'R' or 'r'   C := alpha*B*A + beta*C,

                 Unchanged on exit.


       UPLO (input)
                 On   entry,   UPLO  specifies  whether  the  upper  or  lower
                 triangular  part  of  the  hermitian  matrix   A  is  to   be
                 referenced as follows:

                 UPLO  =  'U'  or  'u'   Only the upper triangular part of the
                 hermitian matrix is to be referenced.

                 UPLO = 'L' or 'l'   Only the lower  triangular  part  of  the
                 hermitian matrix is to be referenced.

                 Unchanged on exit.


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


       N (input)
                 On entry, N specifies the number of columns of the matrix  C.
                 N >= 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  m
                 when  SIDE = 'L' or 'l'  and is n  otherwise.

                 Before  entry  with  SIDE = 'L' or 'l',  the  m by m  part of
                 the array  A  must contain the  hermitian matrix,  such  that
                 when   UPLO = 'U' or 'u', the leading m by m upper triangular
                 part of the array  A  must contain the upper triangular  part
                 of  the  hermitian matrix and the  strictly  lower triangular
                 part of  A  is not referenced,  and when  UPLO = 'L' or  'l',
                 the  leading  m by m  lower triangular part  of the  array  A
                 must  contain  the  lower triangular part  of the   hermitian
                 matrix  and the  strictly upper triangular part of  A  is not
                 referenced.

                 Before entry  with  SIDE = 'R' or 'r',  the  n by n  part  of
                 the  array  A  must contain the  hermitian matrix,  such that
                 when  UPLO = 'U' or 'u', the leading n by n upper  triangular
                 part  of the array  A  must contain the upper triangular part
                 of the  hermitian matrix and the  strictly  lower  triangular
                 part  of  A  is not referenced,  and when  UPLO = 'L' or 'l',
                 the leading  n by n  lower triangular part  of the  array   A
                 must   contain  the  lower triangular part  of the  hermitian
                 matrix and the  strictly upper triangular part of  A  is  not
                 referenced.

                 Note  that the imaginary parts  of the diagonal elements need
                 not be set, they are assumed to be zero.  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 ), otherwise LDA >= max( 1, n ).  Unchanged
                 on exit.


       B (input)
                 COMPLEX*16 array of DIMENSION ( LDB, n ).  Before entry,  the
                 leading  m by n 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.   LDB  must  be  at  least
                 max( 1, m ).  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  updated
                 matrix.


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




                                  7 Nov 2015                         zhemm(3P)