Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

ssyr2 (3p)

Name

ssyr2 - perform the symmetric rank 2 operation A := alpha*x*y' + alpha*y*x' + A

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

void ssyr2(char uplo, int n, float alpha, float *x, int incx, float *y,
int incy, float *a, int lda);

void  ssyr2_64(char  uplo,  long  n,  float alpha, float *x, long incx,
float *y, long incy, float *a, long lda);

Description

Oracle Solaris Studio Performance Library                            ssyr2(3P)



NAME
       ssyr2  -  perform  the  symmetric  rank 2 operation   A := alpha*x*y' +
       alpha*y*x' + A


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

       void ssyr2(char uplo, int n, float alpha, float *x, int incx, float *y,
                 int incy, float *a, int lda);

       void  ssyr2_64(char  uplo,  long  n,  float alpha, float *x, long incx,
                 float *y, long incy, float *a, long lda);



PURPOSE
       ssyr2 performs the  symmetric  rank  2  operation  A  :=  alpha*x*y'  +
       alpha*y*x'  + A, where alpha is a scalar, x and y are n element vectors
       and A is an n by n symmetric 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.


       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.


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


       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.




                                  7 Nov 2015                         ssyr2(3P)