Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zherk (3p)

Name

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

Synopsis

SUBROUTINE ZHERK(UPLO, TRANSA, N, K, ALPHA, A, LDA, BETA, C, LDC)

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

SUBROUTINE ZHERK_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, BETA, C, LDC)

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




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

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

SUBROUTINE HERK_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, BETA,
C, LDC)

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




C INTERFACE
#include <sunperf.h>

void zherk(char uplo, char transa, int n, int k, double alpha,  double-
complex *a, int lda, double beta, doublecomplex *c, int ldc);

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

Description

Oracle Solaris Studio Performance Library                            zherk(3P)



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


SYNOPSIS
       SUBROUTINE ZHERK(UPLO, TRANSA, N, K, ALPHA, A, LDA, BETA, C, LDC)

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

       SUBROUTINE ZHERK_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, BETA, C, LDC)

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




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

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

       SUBROUTINE HERK_64(UPLO, TRANSA, N, K, ALPHA, A, LDA, BETA,
              C, LDC)

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




   C INTERFACE
       #include <sunperf.h>

       void zherk(char uplo, char transa, int n, int k, double alpha,  double-
                 complex *a, int lda, double beta, doublecomplex *c, int ldc);

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



PURPOSE
       zherk  performs  one  of  the  Hermitian  rank  k   operations   C   :=
       alpha*A*conjg( A' ) + beta*C or C := alpha*conjg( A' )*A + beta*C where
       alpha and beta  are  real scalars,  C is an  n by n   Hermitian  matrix
       and   A   is an  n by k  matrix in the  first case and a  k by n matrix
       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( A' ) + beta*C.

                 TRANSA = 'C' or 'c'   C := alpha*conjg( A' )*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   matrix   A,   and  on   entry   with
                 TRANSA = 'C' or 'c',  K  specifies  the number of rows of the
                 matrix A.  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.


       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                         zherk(3P)