Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dspr2 (3p)

Name

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

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                            dspr2(3P)



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


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       dspr2 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, 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)
                 Double precision array, dimension (1  +  (n  -  1)*abs(INCX))
                 Before entry, the incremented array X must contain the n ele-
                 ment 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)
                 Double  precision  array,  dimension  (1 + (n - 1)*abs(INCY))
                 Before entry, the incremented array Y must contain the n ele-
                 ment 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)
                 Double precision array, dimension ((  n*(n  +  1))/2)  Before
                 entry  with  UPLO = 'U' or 'u', the array AP must contain the
                 upper triangular part of the symmetric matrix packed  sequen-
                 tially, column by column, so that AP( 1 ) contains a( 1, 1 ),
                 AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2  )  respec-
                 tively,  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 symmetric matrix packed  sequen-
                 tially, column by column, so that AP( 1 ) contains a( 1, 1 ),
                 AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1  )  respec-
                 tively,  and  so  on. On exit, the array AP is overwritten by
                 the lower triangular part of the updated matrix.




                                  7 Nov 2015                         dspr2(3P)