jadrp


NAME

jadrp, sjadrp, djadrp - right permutation of a jagged diagonal matrix


SYNOPSIS

  SUBROUTINE SJADRP( TRANSP, M, K, VAL, INDX, PNTR, MAXNZ,
 *                   IPERM, WORK, LWORK )
  INTEGER*4  TRANSP, M, K, MAXNZ, LWORK
  INTEGER*4  INDX(*), PNTR(MAXNZ+1), IPERM(K)
  REAL*4     VAL(*), WORK(LWORK)
  SUBROUTINE DJADRP( TRANSP, M, K, VAL, INDX, PNTR, MAXNZ,
 *                     IPERM,WORK,LWORK)
  INTEGER*4  TRANSP, M, K, MAXNZ, LWORK
  INTEGER*4  INDX(*), PNTR(MAXNZ+1), IPERM(K)
  REAL*8     VAL(*), WORK(LWORK)


DESCRIPTION

 A <- A P 
 A <- A P'
                                    ( ' indicates matrix transpose)
 where permutation P is represented by an integer vector IPERM,
 such that IPERM(I) is equal to the position of the only nonzero
 element in row I of permutation matrix P.
 NOTE: In order to get a symetrically permuted jagged diagonal
 matrix P A P', one can explicitly permute the columns P A by
 calling
    SJADRP(0, M, M, VAL, INDX, PNTR, MAXNZ, IPERM, WORK, LWORK)
 where parameters VAL, INDX, PNTR, MAXNZ, IPERM are the representation
 of A in the jagged diagonal format. The operation makes sense if
 the original matrix A is square.


ARGUMENTS

 TRANSP        Indicates how to operate with the permutation matrix
                 0 : operate with matrix
                 1 : operate with transpose matrix
 M             Number of rows in matrix A
 K             Number of columns in matrix A
 VAL()         array of length PNTR(MAXNZ+1)-PNTR(1) 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 PNTR(MAXNZ+1)-PNTR(1) 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 K such that I = IPERM(I'). 
               Array IPERM represents a permutation P, such that
               IPERM(I) is equal to the position of the only nonzero
               element in row I of permutation matrix P.
               For example, if
                              | 0 0 1 |
                          P  =| 1 0 0 |
                              | 0 1 0 |
               then IPERM = (3, 2, 1).
 WORK()        scratch array of length LWORK.  LWORK should be at
               least K.
 LWORK         length of WORK array
               If LWORK = -1, then a workspace query is assumed;
               the routine only calculates the optimal 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

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