djadrp man page on OpenIndiana

Man page or keyword search:  
man Server   20441 pages
apropos Keyword Search (all sections)
Output format
OpenIndiana logo
[printable version]

djadrp(3P)		    Sun Performance Library		    djadrp(3P)

NAME
       djadrp - right permutation of a jagged diagonal matrix

SYNOPSIS
	SUBROUTINE DJADRP( TRANSP, M, K, VAL, INDX, PNTR, MAXNZ,
       *		     IPERM,WORK,LWORK)
	INTEGER	   TRANSP, M, K, MAXNZ, LWORK
	INTEGER	   INDX(*), PNTR(MAXNZ+1), IPERM(K), WORK(LWORK)
	DOUBLE PRECISION VAL(*)

	SUBROUTINE DJADRP_64( TRANSP, M, K, VAL, INDX, PNTR, MAXNZ,
       *		     IPERM,WORK,LWORK)
	INTEGER*8  TRANSP, M, K, MAXNZ, LWORK
	INTEGER*8  INDX(*), PNTR(MAXNZ+1), IPERM(K), WORK(LWORK)
	DOUBLE PRECISION VAL(*)

   F95 INTERFACE
	SUBROUTINE JADRP( TRANSP, M, K, VAL, INDX, PNTR, MAXNZ,
       *		   IPERM, [WORK], [LWORK] )
	INTEGER TRANSP, M, K,  MAXNZ
	INTEGER, DIMENSION(:) :: INDX, PNTR, IPERM
	DOUBLE PRECISION, DIMENSION(:) :: VAL

	SUBROUTINE JADRP_64( TRANSP, M, K, VAL, INDX, PNTR, MAXNZ,
       *		   IPERM, [WORK], [LWORK] )
	INTEGER*8 TRANSP, M, K,	 MAXNZ
	INTEGER*8, DIMENSION(:) :: INDX, PNTR, IPERM
	DOUBLE PRECISION, DIMENSION(:) :: VAL

   C INTERFACE
       #include <sunperf.h>

       void djadrp (const int transp, const int m, const int k, const double*
		 val, const int* indx, int* pntr, const int maxnz, const int*
		 iperm);

       void djadrp_64 (const long transp, const long m, const long k, const
		 double* val, const long* indx, long* pntr, const long maxnz,
		 const long* iperm);

DESCRIPTION
       djadrp performs one of the matrix-matrix operations

       A <- A P	  or	A <- A P'
					  ( ' indicates matrix transpose)

       where  A is an M-by-K sparse matrix represented in the jagged
       diagonal format, the permutation matrix 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

	  DJADRP(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(input)   TRANSP indicates how to operate with the permutation
		       matrix:
			 0 : operate with matrix
			 1 : operate with transpose matrix
		       Unchanged on exit.

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

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

       VAL(input/output)    On entry, VAL is a scalar array of length
		       NNZ=PNTR(MAXNZ+1)-PNTR(1)+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.
		       On exit, VAL contains non-zero entries
		       of the output permuted jagged diagonal matrix.

       INDX(input/output)  On entry, INDX  is an integer array of length
		       NNZ=PNTR(MAXNZ+1)-PNTR(1)+1 consisting of the column
		       indices of the corresponding entries in VAL.
		       On exit, INDX is is overwritten by the column indices
		       of the output permuted jagged diagonal matrix.

       PNTR(input)     On entry, PNTR is an integer  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.
		       Unchanged on exit.

       MAXNZ(input)    On entry,  MAXNZ	 specifies the	max number of
		       nonzeros elements per row. Unchanged on exit.

       IPERM(input)    On entry, IPERM is an 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, 1, 2). Unchanged on exit.

       WORK(workspace)	 Scratch array of length LWORK.	 LWORK should be at
		       least K.

       LWORK(input)    On entry,  LWORK specifies the  length of the array WORK.

		       If LWORK=0, the routine is to allocate workspace needed.

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

SEE ALSO
       Libsunperf SPARSE BLAS is parallelized with the help of OPENMP and it
       is fully	 compatible with NIST FORTRAN Sparse Blas but the sources are
       different.  Libsunperf SPARSE BLAS is free of bugs found in NIST FOR‐
       TRAN Sparse Blas.  Besides several new features and routines are imple‐
       mented.

       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

3rd Berkeley Distribution	  6 Mar 2009			    djadrp(3P)
[top]

List of man pages available for OpenIndiana

Copyright (c) for man pages and the logo by the respective OS vendor.

For those who want to learn more, the polarhome community provides shell access and support.

[legal] [privacy] [GNU] [policy] [cookies] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.
Based on Fawad Halim's script.
....................................................................
Vote for polarhome
Free Shell Accounts :: the biggest list on the net