jadmm


NAME

jadmm, sjadmm, djadmm - Jagged diagonal matrix-matrix multiply (modified Ellpack)


SYNOPSIS

  SUBROUTINE SJADMM( TRANSA, M, N, K, ALPHA, DESCRA,
 *           VAL, INDX, PNTR, MAXNZ, IPERM,
 *           B, LDB, BETA, C, LDC, WORK, LWORK )
  INTEGER*4  TRANSA, M, N, K, DESCRA(5), MAXNZ,
 *           LDB, LDC, LWORK
  INTEGER*4  INDX(NNZ), PNTR(MAXNZ+1), IPERM(M)
  REAL*4     ALPHA, BETA
  REAL*4     VAL(NNZ), B(LDB,*), C(LDC,*), WORK(LWORK)
  SUBROUTINE DJADMM( TRANSA, M, N, K, ALPHA, DESCRA,
 *           VAL, INDX, PNTR, MAXNZ, IPERM,
 *           B, LDB, BETA, C, LDC, WORK, LWORK)
  INTEGER*4  TRANSA, M, N, K, DESCRA(5), MAXNZ,
 *           LDB, LDC, LWORK
  INTEGER*4  INDX(NNZ), PNTR(MAXNZ+1), IPERM(M)
  REAL*8     ALPHA, BETA
  REAL*8     VAL(NNZ), B(LDB,*), C(LDC,*), WORK(LWORK)


DESCRIPTION

 C <- alpha A B + beta C
 C <- alpha A'B + beta C
                                    ( ' indicates matrix transpose)


ARGUMENTS

 TRANSA        Indicates how to operate with the sparse matrix
                 0 : operate with matrix
                 1 : operate with transpose matrix
 M             Number of rows in matrix A
 N             Number of columns in matrix C
 K             Number of columns in matrix A
 ALPHA         Scalar parameter
 DESCRA()      Descriptor argument.  Five element integer array
               DESCRA(1) matrix structure
                 0 : general
                 1 : symmetric
                 2 : Hermitian
                 3 : Triangular
                 4 : Skew(Anti)-Symmetric
                 5 : Diagonal
               DESCRA(2) upper/lower triangular indicator (only used for
                   symmetric and skew-symmetric matrices)
                 1 : lower
                 2 : upper
               DESCRA(3) main diagonal type (NOT IMPLEMENTED)
                 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()         array of length NNZ consisting of entries of A.
               VAL can be viewed as a column major ordering of a    
               row permutation of the Ellpack representation of A, 
               where the Ellpack representation is permuted so that
               the rows are non-increasing in the number of nonzero
               entries.  Values added for padding in Ellpack are
               not included in the Jagged-Diagonal format.
 INDX()        array of length NNZ consisting of the column indices
               of the corresponding entries in VAL.
 PNTR()        array of length MAXNZ+1, where PNTR(I)-PNTR(1)+1
               points to the location in VAL of the first element
               in the row-permuted Ellpack represenation of A.
 MAXNZ         max number of nonzeros elements per row.
 IPERM()       integer array of length M such that I = IPERM(I'), 
               where row I in the original Ellpack representation
               corresponds to row I' in the permuted representation. 
               If IPERM(1) = 0, it is assumed by convention that
               IPERM(I) = I.
 B()           rectangular array with first dimension LDB.
 LDB           leading dimension of B
 BETA          Scalar parameter
 C()           rectangular array with first dimension LDC.
 LDC           leading dimension of C
 WORK()        scratch array of length LWORK.  LWORK should be at least
               MAX(M,N).
 LWORK         length of WORK array


SEE ALSO

NIST FORTRAN Sparse Blas User's Guide available at:

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


NOTES/BUGS

The NIST FORTRAN Sparse BLAS are currently at version 0.5. Some features (including the ones so noted) may not yet be implemented.