vbrsm


NAME

vbrsm, svbrsm, dvbrsm - variable block sparse row format triangular solve


SYNOPSIS

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


DESCRIPTION

 C <- alpha D inv(A) B + beta C    C <- alpha D inv(A') B + beta C
 C <- alpha inv(A) D B + beta C    C <- alpha inv(A') D 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
 MB            Number of block rows in matrix A
 N             Number of columns in matrix C
 UNITD         Type of scaling:
                 1 : Identity matrix (argument DV[] is ignored)
                 2 : Scale on left (row scaling)
                 3 : Scale on right (column scaling)
 DV()          Array containing the diagonal entries of the block
               diagonal matrix D.  The size of the J-th block is
               RPNTR(J+1)-RPNTR(J) and each block contains matrix
               entries stored column-major.  The total length of
               array DV is given by the formula:
               sum over J from 1 to MB:
                 ((RPNTR(J+1)-RPNTR(J))*(RPNTR(J+1)-RPNTR(J)))
 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
                 1 : lower
                 2 : upper
               DESCRA(3) main 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()         scalar array of length NNZ containing matrix entries
               where NNZ is the number of nonzero point entries of a
               matrix A.
               The main diagonal blocks of A must be triangular matrices.
 INDX()        integer array of length BNNZ+1 where BNNZ is the number
               block entries of a 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.
 BINDX()       integer array of length BNNZ consisting of the block column
               indices of the entries of A where BNNZ is the number block
               entries of a matrix A.
 RPNTR()       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).
               Thus, the number of point rows in the I-th block row is
               RPNTR(I+1)-RPNTR(I).
               NOTE:  For the current version CPNTR must equal RPNTR
               and a single array can be passed for both arguments
 CPNTR()       integer array of length MB+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).
               Thus, the number of point columns in the J-th block column is
               CPNTR(J+1)-CPNTR(J).
               NOTE: For the current version CPNTR must equal RPNTR
               and a single array can be passed for both arguments
 BPNTRB()      integer array of length MB such that BPNTRB(I)-BPNTRB(1)+1
               points to location in BINDX of the first block entry of 
               the J-th row of A.
 BPNTRE()      integer array of length MB such that BPNTRE(I)-BPNTRB(1)
               points to location in BINDX of the last block entry of
               the J-th row of A.
 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
               M * MIN(MAX_BLOCK_SIZE, N).
               On exit, if LWORK = -1, WORK(1) returns the minimum value
               for LWORK.
 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.