Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgemv (3p)

Name

cgemv - 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 CGEMV(TRANSA, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

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

SUBROUTINE CGEMV_64(TRANSA, M, N, ALPHA, A, LDA, X, INCX, BETA, Y,
INCY)

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




F95 INTERFACE
SUBROUTINE GEMV(TRANSA, M, N, 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, LDA, INCX, INCY

SUBROUTINE GEMV_64(TRANSA, M, N, 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, LDA, INCX, INCY




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                            cgemv(3P)



NAME
       cgemv  - 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 CGEMV(TRANSA, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)

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

       SUBROUTINE CGEMV_64(TRANSA, M, N, ALPHA, A, LDA, X, INCX, BETA, Y,
             INCY)

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




   F95 INTERFACE
       SUBROUTINE GEMV(TRANSA, M, N, 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, LDA, INCX, INCY

       SUBROUTINE GEMV_64(TRANSA, M, N, 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, LDA, INCX, INCY




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       cgemv  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 matrix.


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
                 >= 0.  Unchanged on exit.


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


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


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


       LDA (input)
                 On  entry, LDA specifies the first dimension of A as declared
                 in the calling (sub) program. LDA >= max( 1, m ).   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
                 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)
                 On entry, INCY specifies the increment for the elements of Y.
                 INCY must not be zero.  Unchanged on exit.




                                  7 Nov 2015                         cgemv(3P)