chpr - perform the hermitian rank 1 operation A := alpha*x*conjg( x' ) + A
SUBROUTINE CHPR(UPLO, N, ALPHA, X, INCX, A) CHARACTER*1 UPLO COMPLEX X(*), A(*) INTEGER N, INCX REAL ALPHA SUBROUTINE CHPR_64(UPLO, N, ALPHA, X, INCX, A) CHARACTER*1 UPLO COMPLEX X(*), A(*) INTEGER*8 N, INCX REAL ALPHA F95 INTERFACE SUBROUTINE HPR(UPLO, N, ALPHA, X, INCX, A) CHARACTER(LEN=1) :: UPLO COMPLEX, DIMENSION(:) :: X, A INTEGER :: N, INCX REAL :: ALPHA SUBROUTINE HPR_64(UPLO, N, ALPHA, X, INCX, A) CHARACTER(LEN=1) :: UPLO COMPLEX, DIMENSION(:) :: X, A INTEGER(8) :: N, INCX REAL :: ALPHA C INTERFACE #include <sunperf.h> void chpr(char uplo, int n, float alpha, complex *x, int incx, complex *a); void chpr_64(char uplo, long n, float alpha, complex *x, long incx, complex *a);
Oracle Solaris Studio Performance Library chpr(3P)
NAME
chpr - perform the hermitian rank 1 operation A := alpha*x*conjg( x'
) + A
SYNOPSIS
SUBROUTINE CHPR(UPLO, N, ALPHA, X, INCX, A)
CHARACTER*1 UPLO
COMPLEX X(*), A(*)
INTEGER N, INCX
REAL ALPHA
SUBROUTINE CHPR_64(UPLO, N, ALPHA, X, INCX, A)
CHARACTER*1 UPLO
COMPLEX X(*), A(*)
INTEGER*8 N, INCX
REAL ALPHA
F95 INTERFACE
SUBROUTINE HPR(UPLO, N, ALPHA, X, INCX, A)
CHARACTER(LEN=1) :: UPLO
COMPLEX, DIMENSION(:) :: X, A
INTEGER :: N, INCX
REAL :: ALPHA
SUBROUTINE HPR_64(UPLO, N, ALPHA, X, INCX, A)
CHARACTER(LEN=1) :: UPLO
COMPLEX, DIMENSION(:) :: X, A
INTEGER(8) :: N, INCX
REAL :: ALPHA
C INTERFACE
#include <sunperf.h>
void chpr(char uplo, int n, float alpha, complex *x, int incx, complex
*a);
void chpr_64(char uplo, long n, float alpha, complex *x, long incx,
complex *a);
PURPOSE
chpr performs the hermitian rank 1 operation A := alpha*x*conjg( x' ) +
A where alpha is a real scalar, x is an n element vector 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.
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.
A (input/output)
( ( 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. On exit, the
array A is overwritten by the upper triangular part of the
updated matrix. Before entry with UPLO = 'L' or 'l', the
array A must contain the lower triangular part of the hermi-
tian 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. On exit, the array A
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 chpr(3P)