NAME

vbrsm, svbrsm, dvbrsm, cvbrsm, zvbrsm - 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)
  SUBROUTINE CVBRSM( 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)
  COMPLEX*8  ALPHA, BETA
  COMPLEX*8  DV(*), VAL(*), B(LDB,*), C(LDC,*), WORK(LWORK)
  SUBROUTINE ZVBRSM( 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)
  COMPLEX*16 ALPHA, BETA
  COMPLEX*16 DV(*), VAL(*), B(LDB,*), C(LDC,*), WORK(LWORK)


DESCRIPTION

   C <- ALPHA  op(A) B + BETA C     C <- ALPHA D op(A) B + BETA C
   C <- ALPHA op(A) D B + BETA C
 where ALPHA and BETA are scalar, C and B are m by n dense matrices,
 D is a block  diagonal matrix,  A is a unit, or non-unit, upper or 
 lower triangular matrix represented in variable block sparse row 
 format and  op( A )  is one  of

  op( A ) = inv(A) or  op( A ) = inv(A')  or  op( A ) =inv(conjg( A' ))
  (inv denotes matrix inverse,  ' indicates matrix transpose)
 All blocks of A on the main diagonal MUST be triangular matrices.


=head1 ARGUMENTS
 TRANSA        Indicates how to operate with the sparse matrix
                 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.
 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 block scaling)
                 3 : Scale on right (column block scaling)
 DV()          Array containing the block 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 (A=A')
                 2 : Hermitian (A= CONJG(A'))
                 3 : Triangular
                 4 : Skew(Anti)-Symmetric (A=-A')
                 5 : Diagonal
                 6 : Skew-Hermitian (A= -CONJG(A'))
               Note: For the routine, DESCRA(1)=3 is only supported.

               DESCRA(2) upper/lower triangular indicator
                 1 : lower
                 2 : upper
               DESCRA(3) main diagonal type
                 0 : non-identity blocks on the main diagonal
                 1 : identity diagonal block
               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 consisting of the block entries 
               of A where each block entry is a dense rectangular matrix 
               stored column by column.
               NNZ is the total number of point entries in all nonzero 
               block  entries of a matrix A.
 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 block entries of A where BNNZ is
               the number block entries of a matrix A.   Block column
               indices MUST be sorted in increasing order for each block
               row.
 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) where M is the number
               of rows  in square triangular matrix A.
               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(MB+1) is set to M+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 I-th block 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 I-th block 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.  
               On exit, if LWORK= -1, WORK(1) returns the optimum  size
               of LWORK.
 LWORK         length of WORK array. LWORK should be at least
               M = RPNTR(MB+1)-RPNTR(1).

               For good performance, LWORK should generally be larger. 
               For optimum performance on multiple processors, LWORK 
               >=M*N_CPUS where N_CPUS is the maximum number of 
               processors available to the program.
               If LWORK=0, the routine is to allocate workspace needed.

               If LWORK = -1, then a workspace query is assumed; the
               routine only calculates the optimum size of the WORK
               array, returns this value as the first entry of the WORK
               array, and no error message related to LWORK is issued
               by XERBLA.


SEE ALSO

NIST FORTRAN Sparse Blas User's Guide available at:

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


NOTES/BUGS

1. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

2. It is known that there exits 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 )