Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zhemv (3p)

Name

zhemv - vector operation y := alpha*A*x + beta*y

Synopsis

SUBROUTINE ZHEMV(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

CHARACTER*1 UPLO
DOUBLE COMPLEX ALPHA, BETA
DOUBLE COMPLEX A(LDA,*), X(*), Y(*)
INTEGER N, LDA, INCX, INCY

SUBROUTINE ZHEMV_64(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

CHARACTER*1 UPLO
DOUBLE COMPLEX ALPHA, BETA
DOUBLE COMPLEX A(LDA,*), X(*), Y(*)
INTEGER*8 N, LDA, INCX, INCY




F95 INTERFACE
SUBROUTINE HEMV(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

CHARACTER(LEN=1) :: UPLO
COMPLEX(8) :: ALPHA, BETA
COMPLEX(8), DIMENSION(:) :: X, Y
COMPLEX(8), DIMENSION(:,:) :: A
INTEGER :: N, LDA, INCX, INCY

SUBROUTINE HEMV_64(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y,
INCY)

CHARACTER(LEN=1) :: UPLO
COMPLEX(8) :: ALPHA, BETA
COMPLEX(8), DIMENSION(:) :: X, Y
COMPLEX(8), DIMENSION(:,:) :: A
INTEGER(8) :: N, LDA, INCX, INCY




C INTERFACE
#include <sunperf.h>

void  zhemv(char  uplo,  int n, doublecomplex *alpha, doublecomplex *a,
int lda, doublecomplex *x,  int  incx,  doublecomplex  *beta,
doublecomplex *y, int incy);

void  zhemv_64(char  uplo,  long n, doublecomplex *alpha, doublecomplex
*a, long lda,  doublecomplex  *x,  long  incx,  doublecomplex
*beta, doublecomplex *y, long incy);

Description

Oracle Solaris Studio Performance Library                            zhemv(3P)



NAME
       zhemv - perform the matrix-vector operation   y := alpha*A*x + beta*y


SYNOPSIS
       SUBROUTINE ZHEMV(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

       CHARACTER*1 UPLO
       DOUBLE COMPLEX ALPHA, BETA
       DOUBLE COMPLEX A(LDA,*), X(*), Y(*)
       INTEGER N, LDA, INCX, INCY

       SUBROUTINE ZHEMV_64(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

       CHARACTER*1 UPLO
       DOUBLE COMPLEX ALPHA, BETA
       DOUBLE COMPLEX A(LDA,*), X(*), Y(*)
       INTEGER*8 N, LDA, INCX, INCY




   F95 INTERFACE
       SUBROUTINE HEMV(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

       CHARACTER(LEN=1) :: UPLO
       COMPLEX(8) :: ALPHA, BETA
       COMPLEX(8), DIMENSION(:) :: X, Y
       COMPLEX(8), DIMENSION(:,:) :: A
       INTEGER :: N, LDA, INCX, INCY

       SUBROUTINE HEMV_64(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y,
              INCY)

       CHARACTER(LEN=1) :: UPLO
       COMPLEX(8) :: ALPHA, BETA
       COMPLEX(8), DIMENSION(:) :: X, Y
       COMPLEX(8), DIMENSION(:,:) :: A
       INTEGER(8) :: N, LDA, INCX, INCY




   C INTERFACE
       #include <sunperf.h>

       void  zhemv(char  uplo,  int n, doublecomplex *alpha, doublecomplex *a,
                 int lda, doublecomplex *x,  int  incx,  doublecomplex  *beta,
                 doublecomplex *y, int incy);

       void  zhemv_64(char  uplo,  long n, doublecomplex *alpha, doublecomplex
                 *a, long lda,  doublecomplex  *x,  long  incx,  doublecomplex
                 *beta, doublecomplex *y, long incy);



PURPOSE
       zhemv  performs  the  matrix-vector   operation y := alpha*A*x + beta*y
       where alpha and beta are scalars, x and y are n element vectors  and  A
       is an n by n hermitian matrix.


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

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

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

                 Unchanged on exit.


       N (input)
                 On entry, N specifies the order of the matrix  A.   N  >=  0.
                 Unchanged on exit.


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


       A (input)
                 Before entry with  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.  Before entry
                 with 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 and 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. LDA >= max( 1, n ).   Unchanged
                 on exit.


       X (input)
                 ( 1 + ( n - 1 )*abs( INCX ) ).  Before entry, the incremented
                 array X must contain the n element vector  x.   Unchanged  on
                 exit.


       INCX (input)
                 On entry, INCX specifies the increment for the elements of X.
                 INCX <> 0.  Unchanged on exit.


       BETA (input)
                 On entry, BETA specifies the scalar beta. When BETA  is  sup-
                 plied  as zero then Y need not be set on input.  Unchanged on
                 exit.


       Y (input/output)
                 ( 1 + ( n - 1 )*abs( INCY ) ).  Before entry, the incremented
                 array  Y  must  contain the n element vector y. On exit, Y is
                 overwritten by the updated vector y.


       INCY (input)
                 On entry, INCY specifies the increment for the elements of Y.
                 INCY <> 0.  Unchanged on exit.




                                  7 Nov 2015                         zhemv(3P)