Contents


NAME

     svbrmm - variable block sparse row format matrix-matrix
     multiply

SYNOPSIS

       SUBROUTINE SVBRMM( TRANSA, MB, N, KB, ALPHA, DESCRA,
      *           VAL, INDX, BINDX, RPNTR, CPNTR, BPNTRB, BPNTRE,
      *           B, LDB, BETA, C, LDC, WORK, LWORK )
       INTEGER    TRANSA, MB, N, KB, DESCRA(5), LDB, LDC, LWORK
       INTEGER    INDX(*), BINDX(*), RPNTR(MB+1), CPNTR(KB+1),
      *           BPNTRB(MB), BPNTRE(MB)
       REAL       ALPHA, BETA
       REAL       VAL(*), B(LDB,*), C(LDC,*), WORK(LWORK)

       SUBROUTINE SVBRMM_64( TRANSA, MB, N, KB, ALPHA, DESCRA,
      *           VAL, INDX, BINDX, RPNTR, CPNTR, BPNTRB, BPNTRE,
      *           B, LDB, BETA, C, LDC, WORK, LWORK )
       INTEGER*8  TRANSA, MB, N, KB, DESCRA(5), LDB, LDC, LWORK
       INTEGER*8  INDX(*), BINDX(*), RPNTR(MB+1), CPNTR(KB+1),
      *           BPNTRB(MB), BPNTRE(MB)
       REAL       ALPHA, BETA
       REAL       VAL(*), B(LDB,*), C(LDC,*), WORK(LWORK)

     F95 INTERFACE

       SUBROUTINE VBRMM(TRANSA, MB, [N], KB, ALPHA, DESCRA,
      *           VAL, INDX, BINDX, RPNTR, CPNTR, BPNTRB, BPNTRE,
      *           B, [LDB], BETA, C,[LDC], [WORK], [LWORK])
       INTEGER    TRANSA, MB, KB
       INTEGER, DIMENSION(:) ::  DESCRA, INDX, BINDX
       INTEGER, DIMENSION(:) ::  RPNTR, CPNTR, BPNTRB, BPNTRE
       REAL    ALPHA, BETA
       REAL, DIMENSION(:) :: VAL
       REAL, DIMENSION(:, :) ::  B, C

       SUBROUTINE VBRMM_64(TRANSA, MB, [N], KB, ALPHA, DESCRA,
      *           VAL, INDX, BINDX, RPNTR, CPNTR, BPNTRB, BPNTRE,
      *           B, [LDB], BETA, C,[LDC], [WORK], [LWORK])
       INTEGER*8    TRANSA, MB, KB
       INTEGER*8, DIMENSION(:) ::  DESCRA, INDX, BINDX
       INTEGER*8, DIMENSION(:) ::  RPNTR, CPNTR, BPNTRB, BPNTRE
       REAL    ALPHA, BETA
       REAL, DIMENSION(:) :: VAL
       REAL, DIMENSION(:, :) ::  B, C

     C INTERFACE

     #include <sunperf.h>
     void svbrmm (int transa, int mb, int n, int kb, float alpha,
     int *descra, float *val, int *indx, int *bindx, int *rpntr,
     int *cpntr, int *bpntrb, int *bpntre, float *b, int ldb,
     float beta, float *c, int ldc);

     void svbrmm_64 (long transa, long mb, long n, long kb,
      float alpha, long *descra, float *val, long *indx,
      long *bindx, long *rpntr, long *cpntr, long *bpntrb,
      long *bpntre, float *b, long ldb, float beta, float *c,
      long ldc);

DESCRIPTION

      svbrmm performs one of the matrix-matrix operations

               C <- alpha op(A) B + beta C

      where alpha and beta are scalars, C and B are  dense matrices,
      A is a sparse M by K matrix represented in the variable block
      sparse row format and op( A )  is one  of

      op( A ) = A   or   op( A ) = A'   or   op( A ) = conjg( A' ).
                                         ( ' indicates matrix transpose)
      The number of rows in A and  the number of columns in A are determined
      as follows

             M=RPNTR(MB+1)-RPNTR(1),  K=CPNTR(KB+1)-CPNTR(1).

ARGUMENTS

      TRANSA(input)   TRANSA specifies the form of op( A ) to be used in
                      the matrix multiplication as follows:
                        0 : operate with matrix
                        1 : operate with transpose matrix
                        2 : operate with the conjugate transpose of matrix.
                          2 is equivalent to 1 if matrix is real.
                      Unchanged on exit.

      MB(input)       On entry, integer MB  specifies the number of block rows
                      in the matrix A. Unchanged on exit.

      N(input)        On entry, integer N specifies the number of columns
                      in the matrix C. Unchanged on exit.

      KB(input)       On entry, integer KB specifies the number of block columns in
                      the matrix A. Unchanged on exit.

      ALPHA(input)    On entry, ALPHA specifies the scalar alpha. Unchanged on exit.
      DESCRA (input)  Descriptor argument.  Five element integer array:
                      DESCRA(1) matrix structure
                        0 : general
                        1 : symmetric (A=A')
                        2 : Hermitian (A= CONJG(A'))
                        3 : Triangular
                        4 : Skew(Anti)-Symmetric (A=-A')
                        5 : Diagonal
                        6 : Skew-Hermitian (A= -CONJG(A'))
                      DESCRA(2) upper/lower triangular indicator
                        1 : lower
                        2 : upper
                      DESCRA(3) main block diagonal type
                        0 : non-unit
                        1 : unit
                      DESCRA(4) Array base (NOT IMPLEMENTED)
                        0 : C/C++ compatible
                        1 : Fortran compatible
                      DESCRA(5) repeated indices? (NOT IMPLEMENTED)
                        0 : unknown
                        1 : no repeated indices

      VAL(input)      On entry,  scalar array VAL of length NNZ consists of the
                      block entries of A where each block entry is a dense
                      rectangular matrix stored column by column where NNZ
                      denotes the total number of point entries in all nonzero
                      block  entries of a matrix A. Unchanged on exit.

      INDX(input)     On entry, INDX is an integer array of length BNNZ+1 where BNNZ is
                      the number of block entries of the matrix A such that the
                      I-th element of INDX[] points to the location in VAL of
                      the (1,1) element of the I-th block entry. Unchanged on exit.

      BINDX(input)    On entry, BINDX is an  integer array of length BNNZ consisting
                      of the block column indices of the block entries of A where
                      BNNZ is the number block entries of the matrix A. Unchanged on
                      exit.

      RPNTR(input)    On entry, RPNTR is an integer array of length MB+1 such that
                      RPNTR(I)-RPNTR(1)+1 is the row index of the first point
                      row in the I-th block row. RPNTR(MB+1) is set to M+RPNTR(1)
                      where M is the number of rows in the matrix A.
                      Thus, the number of point rows in the I-th block row is
                      RPNTR(I+1)-RPNTR(I). Unchanged on exit.

      CPNTR(input)    On entry, CPNTR is an integer array of length KB+1 such that
                      CPNTR(J)-CPNTR(1)+1 is the column index of the first point
                      column in the J-th block column. CPNTR(KB+1) is set to
                      K+CPNTR(1) where K is the number of columns in the matrix A.
                      Thus, the number of point columns in the J-th block column
                      is CPNTR(J+1)-CPNTR(J). Unchanged on exit.
      BPNTRB(input)   On entry, BPNTRB is an integer array of length MB such that
                      BPNTRB(I)-BPNTRB(1)+1 points to location in BINDX of the
                      first block entry of the I-th block row of A.
                      Unchanged on exit.

      BPNTRE(input)   On entry, BPNTRE is an integer array of length MB such that
                      BPNTRE(I)-BPNTRB(1)points to location in BINDX of the
                      last block entry of the I-th block row of A.
                      Unchanged on exit.

      B (input)       Array of DIMENSION ( LDB, N ).
                      Before entry with  TRANSA = 0,  the leading  k by n
                      part of the array  B  must contain the matrix  B,  otherwise
                      the leading  m by n  part of the array  B  must contain  the
                      matrix B. Unchanged on exit.

      LDB (input)     On entry, LDB specifies the first dimension of B as declared
                      in the calling (sub) program. Unchanged on exit.

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

      C(input/output) Array of DIMENSION ( LDC, N ).
                      Before entry with  TRANSA = 0,  the leading  m by n
                      part of the array  C  must contain the matrix C,  otherwise
                      the leading  k by n  part of the array  C must contain  the
                      matrix C. On exit, the array  C  is overwritten by the  matrix
                      ( alpha*op( A )* B  + beta*C ).

      LDC (input)     On entry, LDC specifies the first dimension of C as declared
                      in the calling (sub) program. Unchanged on exit.

      WORK (is not referenced in the current version)

      LWORK (is not referenced in the current version)

SEE ALSO

     Libsunperf  SPARSE BLAS is fully parallel and compatible
     with NIST FORTRAN Sparse Blas but the sources are different.
     Libsunperf SPARSE BLAS is free of bugs found in NIST FORTRAN
     Sparse Blas.  Besides several new features and routines are
     implemented.

     NIST FORTRAN Sparse Blas User's Guide available at:

     http://math.nist.gov/mcsd/Staff/KRemington/fspblas/

     Based on the standard proposed in

     "Document for the Basic Linear Algebra Subprograms (BLAS)
     Standard", University of Tennessee, Knoxville, Tennessee,
     1996:
     http://www.netlib.org/utk/papers/sparse.ps

     The routine is designed so that it provides a possibility to
     use just one sparse matrix representation of a general
     matrix A for computing matrix-matrix multiply for another
     sparse matrix composed  by block triangles and/or the main
     block diagonal of A. The full description of the feature for
     block entry formats is given in section NOTES/BUGS for the
     sbcomm manpage.

NOTES/BUGS
     1. For a general matrix (DESCRA(1)=0), array CPNTR can be
     different from RPNTR.  For all other matrix types,  RPNTR
     must equal CPNTR and a single array can be passed for both
     arguments.

     2. It is known that there exists another representation of
     the variable block sparse row format (see for example
     Y.Saad, "Iterative Methods for Sparse Linear Systems", WPS,
     1996). Its data structure consists of six array instead of
     the seven used in the current implementation.  The main
     difference is that only one array, IA, containing the
     pointers to the beginning of each block row in the array
     BINDX is used instead of two arrays BPNTRB and BPNTRE. To
     use the routine with this kind of variable block sparse row
     format the following calling sequence should be used

       SUBROUTINE SVBRMM( TRANSA, MB, N, KB, ALPHA, DESCRA,
      *           VAL, INDX, BINDX, RPNTR, CPNTR, IA, IA(2),
      *           B, LDB, BETA, C, LDC, WORK, LWORK )