Contents


NAME

     zher -  perform  the  hermitian  rank  1  operation    A  :=
     alpha*x*conjg( x' ) + A

SYNOPSIS

     SUBROUTINE ZHER(UPLO, N, ALPHA, X, INCX, A, LDA)

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

     SUBROUTINE ZHER_64(UPLO, N, ALPHA, X, INCX, A, LDA)

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

  F95 INTERFACE
     SUBROUTINE HER(UPLO, [N], ALPHA, X, [INCX], A, [LDA])

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

     SUBROUTINE HER_64(UPLO, [N], ALPHA, X, [INCX], A, [LDA])

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

  C INTERFACE
     #include <sunperf.h>

     void zher(char uplo, int n, double alpha, doublecomplex  *x,
               int incx, doublecomplex *a, int lda);

     void zher_64(char uplo, long n, double alpha,  doublecomplex
               *x, long incx, doublecomplex *a, long lda);

PURPOSE

     zher  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.

ARGUMENTS

     UPLO (input)
               On entry, UPLO  specifies  whether  the  upper  or
               lower  triangular  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.

     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)
               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. On exit, the  upper  triangular
               part  of  the  array A 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 A must  contain
               the  lower triangular part of the hermitian matrix
               and the strictly upper triangular part of A is not
               referenced.  On exit, the lower triangular part of
               the array A is overwritten by the lower triangular
               part  of  the  updated matrix.  Note that the ima-
               ginary parts of the diagonal elements need not  be
               set, they are assumed to be zero, and on exit they
               are set to zero.

     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.