Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dla_syamv (3p)

Name

dla_syamv - nite matrix to calculate error bounds

Synopsis

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


DOUBLE PRECISION ALPHA, BETA

INTEGER INCX, INCY, LDA, N, UPLO

DOUBLE PRECISION A(LDA,*), X(*), Y(*)


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


DOUBLE PRECISION ALPHA, BETA

INTEGER*8 INCX, INCY, LDA, N, UPLO

DOUBLE PRECISION A(LDA,*), X(*), Y(*)


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


INTEGER :: UPLO, N, LDA, INCX, INCY

REAL(8), DIMENSION(:,:) :: A

REAL(8), DIMENSION(:) :: X, Y

REAL(8) :: ALPHA, BETA


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


INTEGER(8) :: UPLO, N, LDA, INCX, INCY

REAL(8), DIMENSION(:,:) :: A

REAL(8), DIMENSION(:) :: X, Y

REAL(8) :: ALPHA, BETA


C INTERFACE
#include <sunperf.h>

void dla_syamv (int uplo, int n, double alpha, double *a, int lda, dou-
ble *x, int incx, double beta, double *y, int incy);


void dla_syamv_64 (long uplo, long n, double  alpha,  double  *a,  long
lda,  double  *x,  long  incx,  double  beta, double *y, long
incy);

Description

Oracle Solaris Studio Performance Library                        dla_syamv(3P)



NAME
       dla_syamv  -  compute a matrix-vector product using a symmetric indefi-
       nite matrix to calculate error bounds


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


       DOUBLE PRECISION ALPHA, BETA

       INTEGER INCX, INCY, LDA, N, UPLO

       DOUBLE PRECISION A(LDA,*), X(*), Y(*)


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


       DOUBLE PRECISION ALPHA, BETA

       INTEGER*8 INCX, INCY, LDA, N, UPLO

       DOUBLE PRECISION A(LDA,*), X(*), Y(*)


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


       INTEGER :: UPLO, N, LDA, INCX, INCY

       REAL(8), DIMENSION(:,:) :: A

       REAL(8), DIMENSION(:) :: X, Y

       REAL(8) :: ALPHA, BETA


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


       INTEGER(8) :: UPLO, N, LDA, INCX, INCY

       REAL(8), DIMENSION(:,:) :: A

       REAL(8), DIMENSION(:) :: X, Y

       REAL(8) :: ALPHA, BETA


   C INTERFACE
       #include <sunperf.h>

       void dla_syamv (int uplo, int n, double alpha, double *a, int lda, dou-
                 ble *x, int incx, double beta, double *y, int incy);


       void dla_syamv_64 (long uplo, long n, double  alpha,  double  *a,  long
                 lda,  double  *x,  long  incx,  double  beta, double *y, long
                 incy);


PURPOSE
       dla_syamv  performs the matrix-vector operation

       y := alpha*abs(A)*abs(x) + beta*abs(y),

       where alpha and beta are scalars, x and y are vectors and A is an n  by
       n symmetric matrix.

       This  function  is primarily used in calculating error bounds.  To pro-
       tect against underflow during evaluation, components in  the  resulting
       vector  are  perturbed  away  from  zero  by  (N+1) times the underflow
       threshold.  To prevent unnecessarily large errors  for  block-structure
       embedded  in  general  matrices, "symbolically" zero components are not
       perturbed.  A zero entry is considered "symbolic"  if  all  multiplica-
       tions involved in computing that entry have at least one zero multipli-
       cand.


ARGUMENTS
       UPLO (input)
                 UPLO is INTEGER
                 On entry, UPLO specifies whether the upper or lower  triangu-
                 lar part of the array A is to be referenced as follows:
                 UPLO = BLAS_UPPER   Only the upper triangular part of A is to
                 be referenced.
                 UPLO = BLAS_LOWER   Only the lower triangular part of A is to
                 be referenced.
                 Unchanged on exit.


       N (input)
                 N is INTEGER
                 On  entry, N specifies the number of columns of the matrix A.
                 N must be at least zero.
                 Unchanged on exit.


       ALPHA (input)
                 ALPHA is DOUBLE PRECISION
                 On entry, ALPHA specifies the scalar alpha.
                 Unchanged on exit.


       A (input)
                 A is DOUBLE PRECISION array of DIMENSION ( LDA, n )
                 Before entry, the leading m by n part of  the  array  A  must
                 contain the matrix of coefficients.
                 Unchanged on exit.


       LDA (input)
                 LDA is INTEGER
                 On  entry, LDA specifies the first dimension of A as declared
                 in the calling (sub) program. LDA must be at least max( 1,  n
                 ).
                 Unchanged on exit.


       X (input)
                 X is DOUBLE PRECISION array, dimension
                 ( 1 + ( n - 1 )*abs( INCX ) )
                 Before entry, the incremented array X must contain the vector
                 x.
                 Unchanged on exit.


       INCX (input)
                 INCX is INTEGER
                 On entry, INCX specifies the increment for the elements of X.
                 INCX must not be zero.
                 Unchanged on exit.


       BETA (input)
                 BETA is DOUBLE PRECISION
                 On  entry,  BETA specifies the scalar beta. When BETA is sup-
                 plied as zero then Y need not be set on input.
                 Unchanged on exit.


       Y (input/output)
                 Y is DOUBLE PRECISION array, dimension
                 ( 1 + ( n - 1 )*abs( INCY ) )
                 Before entry with BETA non-zero, the incremented array Y must
                 contain  the  vector  y.  On  exit,  Y  is overwritten by the
                 updated vector y.


       INCY (input)
                 INCY is INTEGER
                 On entry, INCY specifies the increment for the elements of Y.
                 INCY must not be zero.
                 Unchanged on exit.




                                  7 Nov 2015                     dla_syamv(3P)