Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zhpmv (3p)

Name

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

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

void  zhpmv(char  uplo,  int n, doublecomplex *alpha, doublecomplex *a,
doublecomplex *x, int incx, doublecomplex  *beta,  doublecom-
plex *y, int incy);

void  zhpmv_64(char  uplo,  long n, doublecomplex *alpha, doublecomplex
*a, doublecomplex *x, long incx, doublecomplex *beta, double-
complex *y, long incy);

Description

Oracle Solaris Studio Performance Library                            zhpmv(3P)



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


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

       void  zhpmv(char  uplo,  int n, doublecomplex *alpha, doublecomplex *a,
                 doublecomplex *x, int incx, doublecomplex  *beta,  doublecom-
                 plex *y, int incy);

       void  zhpmv_64(char  uplo,  long n, doublecomplex *alpha, doublecomplex
                 *a, doublecomplex *x, long incx, doublecomplex *beta, double-
                 complex *y, long incy);



PURPOSE
       zhpmv  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, supplied in packed form.


ARGUMENTS
       UPLO (input)
                 On  entry, UPLO specifies whether the upper or lower triangu-
                 lar part of the matrix A is supplied in the packed array A as
                 follows:

                 UPLO  =  'U'  or 'u'   The upper triangular part of A is sup-
                 plied in A.

                 UPLO = 'L' or 'l'   The lower triangular part of  A  is  sup-
                 plied in A.

                 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)
                 (  ( n*( n + 1 ) )/2 ).  Before entry with UPLO = 'U' or 'u',
                 the array A must contain the upper  triangular  part  of  the
                 hermitian  matrix  packed  sequentially, column by column, so
                 that A( 1 ) contains a( 1, 1 ), A( 2 ) and A( 3 ) contain  a(
                 1,  2  ) and a( 2, 2 ) respectively, and so on.  Before entry
                 with UPLO = 'L' or 'l', the array A must  contain  the  lower
                 triangular  part of the hermitian matrix packed sequentially,
                 column by column, so that A( 1 ) contains a( 1, 1 ), A(  2  )
                 and  A( 3 ) contain a( 2, 1 ) and a( 3, 1 ) respectively, and
                 so on.  Note that the imaginary parts of  the  diagonal  ele-
                 ments  need not be set and are assumed to be zero.  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                         zhpmv(3P)