Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

ssbmv (3p)

Name

ssbmv - vector operation y := alpha*A*x + beta*y

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                            ssbmv(3P)



NAME
       ssbmv - perform the matrix-vector operation   y := alpha*A*x + beta*y


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       ssbmv  performs  the  matrix-vector  operation y := alpha*A*x + beta*y,
       where alpha and beta are scalars, x and y are n element vectors  and  A
       is an n by n symmetric band matrix, with k super-diagonals.


ARGUMENTS
       UPLO (input)
                 On  entry, UPLO specifies whether the upper or lower triangu-
                 lar part of the band matrix A is being supplied as follows:

                 UPLO = 'U' or 'u'   The upper triangular part of A  is  being
                 supplied.

                 UPLO  =  'L' or 'l'   The lower triangular part of A is being
                 supplied.

                 Unchanged on exit.


       N (input)
                 On entry, N specifies the order of the matrix  A.   N  >=  0.
                 Unchanged on exit.


       K (input)
                 On  entry,  K  specifies the number of super-diagonals of the
                 matrix A. K >= 0.  Unchanged on exit.


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


       A (input)
                 Before entry with UPLO = 'U' or 'u', the leading ( k + 1 ) by
                 n part of the array A must contain the upper triangular  band
                 part of the symmetric matrix, supplied column by column, with
                 the leading diagonal of the matrix in row ( k + 1  )  of  the
                 array, the first super-diagonal starting at position 2 in row
                 k, and so on. The top left k by k triangle of the array A  is
                 not  referenced.  The following program segment will transfer
                 the upper triangular part of a  symmetric  band  matrix  from
                 conventional full matrix storage to band storage:

                    DO 20, J = 1, N
                      M = K + 1 - J
                      DO 10, I = MAX( 1, J - K ), J
                        A( M + I, J ) = matrix( I, J )
                 10   CONTINUE
                 20 CONTINUE

                 Before entry with UPLO = 'L' or 'l', the leading ( k + 1 ) by
                 n part of the array A must contain the lower triangular  band
                 part of the symmetric matrix, supplied column by column, with
                 the leading diagonal of the matrix in row 1 of the array, the
                 first  sub-diagonal  starting  at position 1 in row 2, and so
                 on. The bottom right k by k triangle of the array  A  is  not
                 referenced.   The following program segment will transfer the
                 lower triangular part of a symmetric band matrix from conven-
                 tional full matrix storage to band storage:

                    DO 20, J = 1, N
                      M = 1 - J
                      DO 10, I = J, MIN( N, J + K )
                        A( M + I, J ) = matrix( I, J )
                 10   CONTINUE
                 20 CONTINUE

                 Unchanged on exit.


       LDA (input)
                 On  entry, LDA specifies the first dimension of A as declared
                 in the calling (sub) program. LDA >= ( k + 1 ).  Unchanged on
                 exit.


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


       INCX (input)
                 On entry, INCX specifies the increment for the elements of X.
                 INCX <> 0.  Unchanged on exit.


       BETA (input)
                 On entry, BETA specifies the scalar beta.  Unchanged on exit.


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


       INCY (input)
                 On entry, INCY specifies the increment for the elements of Y.
                 INCY <> 0.  Unchanged on exit.




                                  7 Nov 2015                         ssbmv(3P)