Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zhpr2 (3p)

Name

zhpr2 - perform the Hermitian rank 2 operation A := alpha*x*conjg( y' ) + conjg( alpha )*y*conjg( x' ) + A

Synopsis

SUBROUTINE ZHPR2(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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

SUBROUTINE ZHPR2_64(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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




F95 INTERFACE
SUBROUTINE HPR2(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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

SUBROUTINE HPR2_64(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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




C INTERFACE
#include <sunperf.h>

void zhpr2(char uplo, int n, doublecomplex  *alpha,  doublecomplex  *x,
int incx, doublecomplex *y, int incy, doublecomplex *ap);

void  zhpr2_64(char  uplo,  long n, doublecomplex *alpha, doublecomplex
*x, long incx, doublecomplex  *y,  long  incy,  doublecomplex
*ap);

Description

Oracle Solaris Studio Performance Library                            zhpr2(3P)



NAME
       zhpr2 - perform the Hermitian rank 2 operation   A := alpha*x*conjg( y'
       ) + conjg( alpha )*y*conjg( x' ) + A


SYNOPSIS
       SUBROUTINE ZHPR2(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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

       SUBROUTINE ZHPR2_64(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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




   F95 INTERFACE
       SUBROUTINE HPR2(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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

       SUBROUTINE HPR2_64(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)

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




   C INTERFACE
       #include <sunperf.h>

       void zhpr2(char uplo, int n, doublecomplex  *alpha,  doublecomplex  *x,
                 int incx, doublecomplex *y, int incy, doublecomplex *ap);

       void  zhpr2_64(char  uplo,  long n, doublecomplex *alpha, doublecomplex
                 *x, long incx, doublecomplex  *y,  long  incy,  doublecomplex
                 *ap);



PURPOSE
       zhpr2  performs the Hermitian rank 2 operation A := alpha*x*conjg( y' )
       + conjg( alpha )*y*conjg( x' ) + A where alpha is a scalar, 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 AP
                 as follows:

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

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

                 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.


       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.


       Y (input)
                 ( 1 + ( n - 1 )*abs( INCY ) ).  Before entry, the incremented
                 array Y must contain the n element vector  y.   Unchanged  on
                 exit.


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


       AP (input/output)
                 ( ( n*( n + 1 ) )/2 ).  Before entry with  UPLO = 'U' or 'u',
                 the  array  AP  must contain the upper triangular part of the
                 hermitian matrix packed sequentially, column  by  column,  so
                 that  AP( 1 ) contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain
                 a( 1, 2 ) and a( 2, 2 ) respectively, and so on. On exit, the
                 array  AP  is overwritten by the upper triangular part of the
                 updated matrix.  Before entry with UPLO =  'L'  or  'l',  the
                 array AP must contain the lower triangular part of the hermi-
                 tian matrix packed sequentially, column by  column,  so  that
                 AP( 1 ) contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2,
                 1 ) and a( 3, 1 ) respectively, and so on. On exit, the array
                 AP is overwritten by the lower triangular part of the updated
                 matrix.  Note that the imaginary parts of the  diagonal  ele-
                 ments  need  not  be set, they are assumed to be zero, and on
                 exit they are set to zero.




                                  7 Nov 2015                         zhpr2(3P)