Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zher2k (3p)

Name

zher2k - perform one of the Hermitian rank 2k operations C := alpha*A*conjg( B' ) + conjg( alpha )*B*conjg( A' ) + beta*C or C := alpha*conjg( A' )*B + conjg( alpha )*conjg( B' )*A + beta*C

Synopsis

SUBROUTINE ZHER2K(UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB, BETA, C,
LDC)

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

SUBROUTINE ZHER2K_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB, BETA,
C, LDC)

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




F95 INTERFACE
SUBROUTINE HER2K(UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB,
BETA, C, LDC)

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

SUBROUTINE HER2K_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, B,
LDB, BETA, C, LDC)

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




C INTERFACE
#include <sunperf.h>

void zher2k(char uplo, char transa, int n, int k, doublecomplex *alpha,
doublecomplex *a, int lda, doublecomplex *b, int ldb,  double
beta, doublecomplex *c, int ldc);

void  zher2k_64(char  uplo,  char transa, long n, long k, doublecomplex
*alpha, doublecomplex *a, long lda,  doublecomplex  *b,  long
ldb, double beta, doublecomplex *c, long ldc);

Description

Oracle Solaris Studio Performance Library                           zher2k(3P)



NAME
       zher2k  -  perform  one  of  the  Hermitian  rank  2k operations   C :=
       alpha*A*conjg( B' ) + conjg( alpha )*B*conjg( A' ) +  beta*C  or  C  :=
       alpha*conjg( A' )*B + conjg( alpha )*conjg( B' )*A + beta*C


SYNOPSIS
       SUBROUTINE ZHER2K(UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB, BETA, C,
             LDC)

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

       SUBROUTINE ZHER2K_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB, BETA,
             C, LDC)

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




   F95 INTERFACE
       SUBROUTINE HER2K(UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB,
              BETA, C, LDC)

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

       SUBROUTINE HER2K_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, B,
              LDB, BETA, C, LDC)

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




   C INTERFACE
       #include <sunperf.h>

       void zher2k(char uplo, char transa, int n, int k, doublecomplex *alpha,
                 doublecomplex *a, int lda, doublecomplex *b, int ldb,  double
                 beta, doublecomplex *c, int ldc);

       void  zher2k_64(char  uplo,  char transa, long n, long k, doublecomplex
                 *alpha, doublecomplex *a, long lda,  doublecomplex  *b,  long
                 ldb, double beta, doublecomplex *c, long ldc);



PURPOSE
       zher2k   performs  one  of  the  Hermitian  rank  2k  operations  C  :=
       alpha*A*conjg( B' ) + conjg( alpha )*B*conjg( A' ) +  beta*C  or  C  :=
       alpha*conjg(  A'  )*B  +  conjg(  alpha  )*conjg( B' )*A + beta*C where
       alpha and beta  are scalars with  beta  real,  C is an  n by  n  Hermi-
       tian matrix and  A and B  are  n by k matrices in the first case and  k
       by n  matrices in the second case.


ARGUMENTS
       UPLO (input)
                 On  entry,   UPLO  specifies  whether  the  upper  or   lower
                 triangular   part  of the  array  C  is to be  referenced  as
                 follows:

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

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

                 Unchanged on exit.


       TRANSA (input)
                 On entry,  TRANSA  specifies the operation to be performed as
                 follows:

                 TRANSA  =  'N'  or 'n'    C := alpha*A*conjg( B' )          +
                 conjg( alpha )*B*conjg( A' ) + beta*C.

                 TRANSA = 'C' or 'c'    C := alpha*conjg(  A'  )*B           +
                 conjg( alpha )*conjg( B' )*A + beta*C.

                 Unchanged on exit.


       N (input)
                 On  entry,  N specifies the order of the matrix C.  N must be
                 at least zero.  Unchanged on exit.


       K (input)
                 On entry with  TRANSA = 'N' or 'n',  K  specifies  the number
                 of   columns  of the  matrices  A and B,  and on  entry  with
                 TRANSA = 'C' or 'c',  K  specifies  the number of rows of the
                 matrices   A  and  B.  K must be at least zero.  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  n  otherwise.   Before
                 entry  with   TRANSA = 'N' or 'n',  the  leading  n by k part
                 of the array  A  must contain the matrix  A,   otherwise  the
                 leading   k  by  n   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 must be at least  max( 1, n ), otherwise  LDA  must
                 be at least  max( 1, k ).  Unchanged on exit.


       B (input)
                 COMPLEX*16        array of DIMENSION ( LDB, kb ), where kb is
                 k  when  TRANSA = 'N' or 'n',  and is  n  otherwise.   Before
                 entry  with   TRANSA = 'N' or 'n',  the  leading  n by k part
                 of the array  B  must contain the matrix  B,   otherwise  the
                 leading   k  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.   When  TRANSA = 'N' or 'n'
                 then  LDB must be at least  max( 1, n ), otherwise  LDB  must
                 be at least  max( 1, k ).  Unchanged on exit.


       BETA (input)
                 On entry, BETA specifies the scalar beta.  Unchanged on exit.


       C (input/output)
                 COMPLEX*16       array of DIMENSION ( LDC, n ).

                 Before entry  with  UPLO = 'U' or 'u',  the leading  n  by  n
                 upper  triangular  part of the array C must contain the upper
                 triangular part  of the  Hermitian matrix  and  the  strictly
                 lower  triangular  part of C is not referenced.  On exit, the
                 upper triangular part of the array  C is overwritten  by  the
                 upper triangular part of the updated matrix.

                 Before  entry   with  UPLO = 'L' or 'l',  the leading  n by n
                 lower triangular part of the array C must contain  the  lower
                 triangular  part   of the  Hermitian matrix  and the strictly
                 upper triangular part of C is not referenced.  On  exit,  the
                 lower  triangular  part of the array  C is overwritten by the
                 lower triangular part of the updated matrix.

                 Note that the imaginary parts of the diagonal  elements  need
                 not  be  set,  they are assumed to be zero,  and on exit they
                 are set to zero.


       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, n ).  Unchanged on exit.




                                  7 Nov 2015                        zher2k(3P)