Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cla_gbamv (3p)

Name

cla_gbamv - vector operation to calculate error bounds

Synopsis

SUBROUTINE CLA_GBAMV(TRANS, M, N, KL, KU, ALPHA,  AB,  LDAB,  X,  INCX,
BETA, Y, INCY)


REAL ALPHA, BETA

INTEGER INCX, INCY, LDAB, M, N, KL, KU, TRANS

COMPLEX AB(LDAB,*), X(*)

REAL Y(*)


SUBROUTINE  CLA_GBAMV_64(TRANS, M, N, KL, KU, ALPHA, AB, LDAB, X, INCX,
BETA, Y, INCY)


REAL ALPHA, BETA

INTEGER*8 INCX, INCY, LDAB, M, N, KL, KU, TRANS

COMPLEX AB(LDAB,*), X(*)

REAL Y(*)


F95 INTERFACE
SUBROUTINE LA_GBAMV(TRANS, M, N, KL, KU,  ALPHA,  AB,  LDAB,  X,  INCX,
BETA, Y, INCY)


INTEGER :: TRANS, M, N, KL, KU, LDAB, INCX, INCY

REAL, DIMENSION(:) :: Y

COMPLEX, DIMENSION(:) :: X

COMPLEX, DIMENSION(:,:) :: AB

REAL :: ALPHA, BETA


SUBROUTINE  LA_GBAMV_64(TRANS,  M, N, KL, KU, ALPHA, AB, LDAB, X, INCX,
BETA, Y, INCY)


INTEGER(8) :: TRANS, M, N, KL, KU, LDAB, INCX, INCY

REAL, DIMENSION(:) :: Y

COMPLEX, DIMENSION(:) :: X

COMPLEX, DIMENSION(:,:) :: AB

REAL :: ALPHA, BETA


C INTERFACE
#include <sunperf.h>

void cla_gbamv (int trans, int m, int n, int kl, int ku,  float  alpha,
floatcomplex  *ab, int ldab, floatcomplex *x, int incx, float
beta, float *y, int incy);


void cla_gbamv_64 (long trans, long m, long n, long kl, long ku,  float
alpha,  floatcomplex  *ab,  long  ldab, floatcomplex *x, long
incx, float beta, float *y, long incy);

Description

Oracle Solaris Studio Performance Library                        cla_gbamv(3P)



NAME
       cla_gbamv - perform a matrix-vector operation to calculate error bounds


SYNOPSIS
       SUBROUTINE CLA_GBAMV(TRANS, M, N, KL, KU, ALPHA,  AB,  LDAB,  X,  INCX,
                 BETA, Y, INCY)


       REAL ALPHA, BETA

       INTEGER INCX, INCY, LDAB, M, N, KL, KU, TRANS

       COMPLEX AB(LDAB,*), X(*)

       REAL Y(*)


       SUBROUTINE  CLA_GBAMV_64(TRANS, M, N, KL, KU, ALPHA, AB, LDAB, X, INCX,
                 BETA, Y, INCY)


       REAL ALPHA, BETA

       INTEGER*8 INCX, INCY, LDAB, M, N, KL, KU, TRANS

       COMPLEX AB(LDAB,*), X(*)

       REAL Y(*)


   F95 INTERFACE
       SUBROUTINE LA_GBAMV(TRANS, M, N, KL, KU,  ALPHA,  AB,  LDAB,  X,  INCX,
                 BETA, Y, INCY)


       INTEGER :: TRANS, M, N, KL, KU, LDAB, INCX, INCY

       REAL, DIMENSION(:) :: Y

       COMPLEX, DIMENSION(:) :: X

       COMPLEX, DIMENSION(:,:) :: AB

       REAL :: ALPHA, BETA


       SUBROUTINE  LA_GBAMV_64(TRANS,  M, N, KL, KU, ALPHA, AB, LDAB, X, INCX,
                 BETA, Y, INCY)


       INTEGER(8) :: TRANS, M, N, KL, KU, LDAB, INCX, INCY

       REAL, DIMENSION(:) :: Y

       COMPLEX, DIMENSION(:) :: X

       COMPLEX, DIMENSION(:,:) :: AB

       REAL :: ALPHA, BETA


   C INTERFACE
       #include <sunperf.h>

       void cla_gbamv (int trans, int m, int n, int kl, int ku,  float  alpha,
                 floatcomplex  *ab, int ldab, floatcomplex *x, int incx, float
                 beta, float *y, int incy);


       void cla_gbamv_64 (long trans, long m, long n, long kl, long ku,  float
                 alpha,  floatcomplex  *ab,  long  ldab, floatcomplex *x, long
                 incx, float beta, float *y, long incy);


PURPOSE
       cla_gbamv  performs one of the matrix-vector operations
       y := alpha*abs(A)*abs(x) + beta*abs(y),
       or y := alpha*abs(A)**T*abs(x) + beta*abs(y),
       where alpha and beta are scalars, x and y are vectors and A is an m  by
       n 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 multiplications
       involved in computing that entry have at least one zero multiplicand.


ARGUMENTS
       TRANS (input)
                 TRANS is INTEGER
                 On  entry,  TRANS  specifies the operation to be performed as
                 follows:
                 BLAS_NO_TRANS    y:=alpha*abs(A)*abs(x)+beta*abs(y)
                 BLAS_TRANS       y:=alpha*abs(A**T)*abs(x)+beta*abs(y)
                 BLAS_CONJ_TRANS  y:=alpha*abs(A**T)*abs(x)+beta*abs(y)
                 Unchanged on exit.


       M (input)
                 M is INTEGER
                 On entry, M specifies the number of rows of the matrix A.
                 M must be at least zero.
                 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.


       KL (input)
                 KL is INTEGER
                 The number of subdiagonals within the band of A. KL >= 0.


       KU (input)
                 KU is INTEGER
                 The number of superdiagonals within the band of A. KU >= 0.


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


       AB (input)
                 AB is COMPLEX array, dimension (LDAB,n)
                 Before  entry,  the  leading m by n part of the array AB must
                 contain the matrix of coefficients.
                 Unchanged on exit.


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


       X (input)
                 X is COMPLEX array, dimension
                 ( 1 + (n - 1)*abs(INCX)) when TRANS = '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)
                 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 REAL
                 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 REAL array, dimension
                 ( 1 + (m - 1)*abs(INCY)) when TRANS = '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)
                 INCY is INTEGER
                 On entry, INCY specifies the increment for the elements of Y.
                 INCY must not be zero.
                 Unchanged on exit.
                 Level 2 Blas routine.




                                  7 Nov 2015                     cla_gbamv(3P)