Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dspr (3p)

Name

dspr - perform the symmetric rank 1 operation A := alpha*x*x' + A

Synopsis

SUBROUTINE DSPR(UPLO, N, ALPHA, X, INCX, A)

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

SUBROUTINE DSPR_64(UPLO, N, ALPHA, X, INCX, A)

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




F95 INTERFACE
SUBROUTINE SPR(UPLO, N, ALPHA, X, INCX, A)

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

SUBROUTINE SPR_64(UPLO, N, ALPHA, X, INCX, A)

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




C INTERFACE
#include <sunperf.h>

void  dspr(char  uplo, int n, double alpha, double *x, int incx, double
*a);

void dspr_64(char uplo, long n, double alpha,  double  *x,  long  incx,
double *a);

Description

Oracle Solaris Studio Performance Library                             dspr(3P)



NAME
       dspr - perform the symmetric rank 1 operation   A := alpha*x*x' + A


SYNOPSIS
       SUBROUTINE DSPR(UPLO, N, ALPHA, X, INCX, A)

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

       SUBROUTINE DSPR_64(UPLO, N, ALPHA, X, INCX, A)

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




   F95 INTERFACE
       SUBROUTINE SPR(UPLO, N, ALPHA, X, INCX, A)

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

       SUBROUTINE SPR_64(UPLO, N, ALPHA, X, INCX, A)

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




   C INTERFACE
       #include <sunperf.h>

       void  dspr(char  uplo, int n, double alpha, double *x, int incx, double
                 *a);

       void dspr_64(char uplo, long n, double alpha,  double  *x,  long  incx,
                 double *a);



PURPOSE
       dspr performs the symmetric rank 1 operation A := alpha*x*x' + A, where
       alpha is a real scalar, x is an n element vector 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 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
                 symmetric 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 symmet-
                 ric 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.




                                  7 Nov 2015                          dspr(3P)