Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgbmv (3p)

Name

cgbmv - vector operations y:=alpha*A*x + beta*y, or y:=alpha*A'*x + beta*y, or y:=alpha*conjg(A')*x + beta*y

Synopsis

SUBROUTINE CGBMV(TRANSA, M, N, KL, KU, ALPHA, A, LDA, X, INCX,
BETA, Y, INCY)

CHARACTER*1 TRANSA
COMPLEX ALPHA, BETA
COMPLEX A(LDA,*), X(*), Y(*)
INTEGER M, N, KL, KU, LDA, INCX, INCY

SUBROUTINE CGBMV_64(TRANSA, M, N, KL, KU, ALPHA, A, LDA, X,
INCX, BETA, Y, INCY)

CHARACTER*1 TRANSA
COMPLEX ALPHA, BETA
COMPLEX A(LDA,*), X(*), Y(*)
INTEGER*8 M, N, KL, KU, LDA, INCX, INCY




F95 INTERFACE
SUBROUTINE GBMV(TRANSA, M, N, KL, KU, ALPHA, A, LDA, X,
INCX, BETA, Y, INCY)

CHARACTER(LEN=1) :: TRANSA
COMPLEX :: ALPHA, BETA
COMPLEX, DIMENSION(:) :: X, Y
COMPLEX, DIMENSION(:,:) :: A
INTEGER :: M, N, KL, KU, LDA, INCX, INCY

SUBROUTINE GBMV_64(TRANSA, M, N, KL, KU, ALPHA, A, LDA,
X, INCX, BETA, Y, INCY)

CHARACTER(LEN=1) :: TRANSA
COMPLEX :: ALPHA, BETA
COMPLEX, DIMENSION(:) :: X, Y
COMPLEX, DIMENSION(:,:) :: A
INTEGER(8) :: M, N, KL, KU, LDA, INCX, INCY




C INTERFACE
#include <sunperf.h>

void cgbmv(char transa, int m, int n, int kl, int ku,  complex  *alpha,
complex  *a,  int  lda,  complex *x, int incx, complex *beta,
complex *y, int incy);

void cgbmv_64(char transa, long m, long n, long kl,  long  ku,  complex
*alpha,  complex *a, long lda, complex *x, long incx, complex
*beta, complex *y, long incy);

Description

Oracle Solaris Studio Performance Library                            cgbmv(3P)



NAME
       cgbmv  -  perform  one  of  the matrix-vector operations y:=alpha*A*x +
       beta*y, or y:=alpha*A'*x + beta*y, or y:=alpha*conjg(A')*x + beta*y


SYNOPSIS
       SUBROUTINE CGBMV(TRANSA, M, N, KL, KU, ALPHA, A, LDA, X, INCX,
             BETA, Y, INCY)

       CHARACTER*1 TRANSA
       COMPLEX ALPHA, BETA
       COMPLEX A(LDA,*), X(*), Y(*)
       INTEGER M, N, KL, KU, LDA, INCX, INCY

       SUBROUTINE CGBMV_64(TRANSA, M, N, KL, KU, ALPHA, A, LDA, X,
             INCX, BETA, Y, INCY)

       CHARACTER*1 TRANSA
       COMPLEX ALPHA, BETA
       COMPLEX A(LDA,*), X(*), Y(*)
       INTEGER*8 M, N, KL, KU, LDA, INCX, INCY




   F95 INTERFACE
       SUBROUTINE GBMV(TRANSA, M, N, KL, KU, ALPHA, A, LDA, X,
              INCX, BETA, Y, INCY)

       CHARACTER(LEN=1) :: TRANSA
       COMPLEX :: ALPHA, BETA
       COMPLEX, DIMENSION(:) :: X, Y
       COMPLEX, DIMENSION(:,:) :: A
       INTEGER :: M, N, KL, KU, LDA, INCX, INCY

       SUBROUTINE GBMV_64(TRANSA, M, N, KL, KU, ALPHA, A, LDA,
              X, INCX, BETA, Y, INCY)

       CHARACTER(LEN=1) :: TRANSA
       COMPLEX :: ALPHA, BETA
       COMPLEX, DIMENSION(:) :: X, Y
       COMPLEX, DIMENSION(:,:) :: A
       INTEGER(8) :: M, N, KL, KU, LDA, INCX, INCY




   C INTERFACE
       #include <sunperf.h>

       void cgbmv(char transa, int m, int n, int kl, int ku,  complex  *alpha,
                 complex  *a,  int  lda,  complex *x, int incx, complex *beta,
                 complex *y, int incy);

       void cgbmv_64(char transa, long m, long n, long kl,  long  ku,  complex
                 *alpha,  complex *a, long lda, complex *x, long incx, complex
                 *beta, complex *y, long incy);



PURPOSE
       cgbmv performs one of the matrix-vector operations  y  :=  alpha*A*x  +
       beta*y,  or  y  := alpha*A'*x + beta*y, or   y := alpha*conjg( A' )*x +
       beta*y where alpha and beta are scalars, x and y are vectors and  A  is
       an m by n band matrix, with kl sub-diagonals and ku super-diagonals.


ARGUMENTS
       TRANSA (input)
                 On  entry,  TRANSA specifies the operation to be performed as
                 follows:
                 TRANSA = 'N' or 'n'   y := alpha*A*x + beta*y.
                 TRANSA = 'T' or 't'   y := alpha*A'*x + beta*y.
                 TRANSA = 'C' or 'c'   y := alpha*conjg( A' )*x + beta*y.
                 Unchanged on exit.


       M (input)
                 On entry, M specifies the number of rows of the matrix A.   M
                 must be at least zero.  Unchanged on exit.


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


       KL (input)
                 On entry, KL specifies the number  of  sub-diagonals  of  the
                 matrix A. KL must satisfy  0 .le. KL.  Unchanged on exit.


       KU (input)
                 On  entry,  KU specifies the number of super-diagonals of the
                 matrix A. KU must satisfy  0 .le. KU.  Unchanged on exit.


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


       A (input)
                 Before  entry,  the  leading ( kl + ku + 1 ) by n part of the
                 array A must contain the  matrix  of  coefficients,  supplied
                 column  by column, with the leading diagonal of the matrix in
                 row ( ku + 1 ) of the array, the first super-diagonal  start-
                 ing  at position 2 in row ku, the first sub-diagonal starting
                 at position 1 in row ( ku + 2 ), and so on.  Elements in  the
                 array A that do not correspond to elements in the band matrix
                 (such as the top left ku by ku triangle) are not  referenced.
                 The  following  program  segment  will transfer a band matrix
                 from conventional full matrix storage to band storage:

                    DO 20, J = 1, N
                      K = KU + 1 - J
                      DO 10, I = MAX( 1, J-KU ), MIN( M, J+KL )
                        A( K + 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 must be at least ( kl + ku
                 + 1 ).  Unchanged on exit.


       X (input)
                 ( 1 + ( n - 1 )*abs( INCX ) ) when TRANSA = 'N' or 'n' and at
                 least ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.  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 must not be zero.  Unchanged on exit.


       BETA (input)
                 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)
                 ( 1 + ( m - 1 )*abs( INCY ) ) when TRANSA = 'N' or 'n' and at
                 least ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.  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 must not be zero.  Unchanged on exit.




                                  7 Nov 2015                         cgbmv(3P)