zcsrmm - matrix multiply
SUBROUTINE ZCSRMM( TRANSA, M, N, K, ALPHA, DESCRA, * VAL, INDX, PNTRB, PNTRE, * B, LDB, BETA, C, LDC, WORK, LWORK) INTEGER TRANSA, M, N, K, DESCRA(5), * LDB, LDC, LWORK INTEGER INDX(NNZ), PNTRB(M), PNTRE(M) DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX VAL(NNZ), B(LDB,*), C(LDC,*), WORK(LWORK) SUBROUTINE ZCSRMM_64( TRANSA, M, N, K, ALPHA, DESCRA, * VAL, INDX, PNTRB, PNTRE, * B, LDB, BETA, C, LDC, WORK, LWORK) INTEGER*8 TRANSA, M, N, K, DESCRA(5), * LDB, LDC, LWORK INTEGER*8 INDX(NNZ), PNTRB(M), PNTRE(M) DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX VAL(NNZ), B(LDB,*), C(LDC,*), WORK(LWORK) where NNZ = PNTRE(M)-PNTRB(1) F95 INTERFACE SUBROUTINE CSRMM( TRANSA, M, N, K, ALPHA, DESCRA, VAL, INDX, * PNTRB, PNTRE, B, LDB, BETA, C, LDC, WORK, LWORK ) INTEGER TRANSA, M, K INTEGER, DIMENSION(:) :: DESCRA, INDX, PNTRB, PNTRE DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX, DIMENSION(:) :: VAL DOUBLE COMPLEX, DIMENSION(:, :) :: B, C SUBROUTINE CSRMM_64( TRANSA, M, N, K, ALPHA, DESCRA, VAL, INDX, * PNTRB, PNTRE, B, LDB, BETA, C, LDC, WORK, LWORK ) INTEGER*8 TRANSA, M, K INTEGER*8, DIMENSION(:) :: DESCRA, INDX, PNTRB, PNTRE DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX, DIMENSION(:) :: VAL DOUBLE COMPLEX, DIMENSION(:, :) :: B, C C INTERFACE #include <sunperf.h> void zcsrmm (const int transa, const int m, const int n, const int k, const doublecomplex* alpha, const int* descra, const double- complex* val, const int* indx, const int* pntrb, const int* pntre, const doublecomplex* b, const int ldb, const double- complex* beta, doublecomplex* c, const int ldc); void zcsrmm_64 (const long transa, const long m, const long n, const long k, const doublecomplex* alpha, const long* descra, const doublecomplex* val, const long* indx, const long* pntrb, const long* pntre, const doublecomplex* b, const long ldb, const doublecomplex* beta, doublecomplex* c, const long ldc);
Oracle Solaris Studio Performance Library zcsrmm(3P) NAME zcsrmm - compressed sparse row format matrix-matrix multiply SYNOPSIS SUBROUTINE ZCSRMM( TRANSA, M, N, K, ALPHA, DESCRA, * VAL, INDX, PNTRB, PNTRE, * B, LDB, BETA, C, LDC, WORK, LWORK) INTEGER TRANSA, M, N, K, DESCRA(5), * LDB, LDC, LWORK INTEGER INDX(NNZ), PNTRB(M), PNTRE(M) DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX VAL(NNZ), B(LDB,*), C(LDC,*), WORK(LWORK) SUBROUTINE ZCSRMM_64( TRANSA, M, N, K, ALPHA, DESCRA, * VAL, INDX, PNTRB, PNTRE, * B, LDB, BETA, C, LDC, WORK, LWORK) INTEGER*8 TRANSA, M, N, K, DESCRA(5), * LDB, LDC, LWORK INTEGER*8 INDX(NNZ), PNTRB(M), PNTRE(M) DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX VAL(NNZ), B(LDB,*), C(LDC,*), WORK(LWORK) where NNZ = PNTRE(M)-PNTRB(1) F95 INTERFACE SUBROUTINE CSRMM( TRANSA, M, N, K, ALPHA, DESCRA, VAL, INDX, * PNTRB, PNTRE, B, LDB, BETA, C, LDC, WORK, LWORK ) INTEGER TRANSA, M, K INTEGER, DIMENSION(:) :: DESCRA, INDX, PNTRB, PNTRE DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX, DIMENSION(:) :: VAL DOUBLE COMPLEX, DIMENSION(:, :) :: B, C SUBROUTINE CSRMM_64( TRANSA, M, N, K, ALPHA, DESCRA, VAL, INDX, * PNTRB, PNTRE, B, LDB, BETA, C, LDC, WORK, LWORK ) INTEGER*8 TRANSA, M, K INTEGER*8, DIMENSION(:) :: DESCRA, INDX, PNTRB, PNTRE DOUBLE COMPLEX ALPHA, BETA DOUBLE COMPLEX, DIMENSION(:) :: VAL DOUBLE COMPLEX, DIMENSION(:, :) :: B, C C INTERFACE #include <sunperf.h> void zcsrmm (const int transa, const int m, const int n, const int k, const doublecomplex* alpha, const int* descra, const double- complex* val, const int* indx, const int* pntrb, const int* pntre, const doublecomplex* b, const int ldb, const double- complex* beta, doublecomplex* c, const int ldc); void zcsrmm_64 (const long transa, const long m, const long n, const long k, const doublecomplex* alpha, const long* descra, const doublecomplex* val, const long* indx, const long* pntrb, const long* pntre, const doublecomplex* b, const long ldb, const doublecomplex* beta, doublecomplex* c, const long ldc); DESCRIPTION zcsrmm performs one of the matrix-matrix operations C <- alpha op(A) B + beta C where op( A ) is one of op( A ) = A or op( A ) = A' or op( A ) = conjg( A' ) ( ' indicates matrix transpose), A is an M-by-K sparse matrix represented in the compressed sparse row format, alpha and beta are scalars, C and B are dense matrices. ARGUMENTS TRANSA(input) TRANSA specifies the form of op( A ) to be used in the matrix multiplication as follows: 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. Unchanged on exit. M(input) On entry, M specifies the number of rows in the matrix A. Unchanged on exit. N(input) On entry, N specifies the number of columns in the matrix C. Unchanged on exit. K(input) On entry, K specifies the number of columns in the matrix A. Unchanged on exit. ALPHA(input) On entry, ALPHA specifies the scalar alpha. Unchanged on exit. DESCRA (input) 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')) 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(input) On entry, VAL is a scalar array of length NNZ = PNTRE(M)-PNTRB(1) consisting of nonzero entries of A. Unchanged on exit. INDX(input) On entry, INDX is an integer array of length NNZ = PNTRE(M)-PNTRB(1) consisting of the column indices of nonzero entries of A. Unchanged on exit. PNTRB(input) On entry, PNTRB is an integer array of length M such that PNTRB(J)-PNTRB(1)+1 points to location in VAL of the first nonzero element in row J. Unchanged on exit. PNTRE(input) On entry, PNTRE is an integer array of length M such that PNTRE(J)-PNTRB(1) points to location in VAL of the last nonzero element in row J. Unchanged on exit. B (input) Array of DIMENSION ( LDB, N ). Before entry with TRANSA = 0, the leading k by n part of the array B must contain the matrix B, otherwise the leading m by n part of the array B must contain the matrix B. Unchanged on exit. LDB (input) On entry, LDB specifies the first dimension of B as declared in the calling (sub) program. Unchanged on exit. BETA (input) On entry, BETA specifies the scalar beta. Unchanged on exit. C(input/output) Array of DIMENSION ( LDC, N ). Before entry with TRANSA = 0, the leading m by n part of the array C must contain the matrix C, otherwise the leading k by n part of the array C must contain the matrix C. On exit, the array C is overwritten by the matrix ( alpha*op( A )* B + beta*C ). LDC (input) On entry, LDC specifies the first dimension of C as declared in the calling (sub) program. Unchanged on exit. WORK (is not referenced in the current version) LWORK (is not referenced in the current version) SEE ALSO Libsunperf SPARSE BLAS is fully parallel and compatible with NIST FOR- TRAN Sparse Blas but the sources are different. Libsunperf SPARSE BLAS is free of bugs found in NIST FORTRAN Sparse Blas. Besides several new features and routines are implemented. 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 The routine is designed so that it provides a possibility to use just one sparse matrix representation of a general matrix A for computing matrix-matrix multiply for another sparse matrix composed by trian- gles and/or the main diagonal of A. The full description of the feature for point entry formats in the case of complex matrices is given in section NOTES/BUGS for the ccoomm manpage. NOTES/BUGS It is known that there exists another representation of the compressed sparse row format (see for example Y.Saad, "Iterative Methods for Sparse Linear Systems", WPS, 1996). Its data structure consists of three array instead of the four used in the current implementation. The main difference is that only one array, IA, containing the pointers to the beginning of each row in the arrays VAL and INDX is used instead of two arrays PNTRB and PNTRE. To use the routine with this kind of compressed sparse row format the following calling sequence should be used SUBROUTINE ZCSRMM( TRANSA, M, N, K, ALPHA, DESCRA, * VAL, INDX, IA, IA(2), B, LDB, BETA, * C, LDC, WORK, LWORK ) 3rd Berkeley Distribution 7 Nov 2015 zcsrmm(3P)