SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ pb_pdlaprnt()

subroutine pb_pdlaprnt ( integer  m,
integer  n,
double precision, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca,
integer  irprnt,
integer  icprnt,
character*(*)  cmatnm,
integer  nout,
double precision, dimension( * )  work 
)

Definition at line 8632 of file pdblastst.f.

8634*
8635* -- PBLAS test routine (version 2.0) --
8636* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
8637* and University of California, Berkeley.
8638* April 1, 1998
8639*
8640* .. Scalar Arguments ..
8641 INTEGER IA, ICPRNT, IRPRNT, JA, M, N, NOUT
8642* ..
8643* .. Array Arguments ..
8644 CHARACTER*(*) CMATNM
8645 INTEGER DESCA( * )
8646 DOUBLE PRECISION A( * ), WORK( * )
8647* ..
8648*
8649* Purpose
8650* =======
8651*
8652* PB_PDLAPRNT prints to the standard output a submatrix sub( A ) deno-
8653* ting A(IA:IA+M-1,JA:JA+N-1). The local pieces are sent and printed by
8654* the process of coordinates (IRPRNT, ICPRNT).
8655*
8656* Notes
8657* =====
8658*
8659* A description vector is associated with each 2D block-cyclicly dis-
8660* tributed matrix. This vector stores the information required to
8661* establish the mapping between a matrix entry and its corresponding
8662* process and memory location.
8663*
8664* In the following comments, the character _ should be read as
8665* "of the distributed matrix". Let A be a generic term for any 2D
8666* block cyclicly distributed matrix. Its description vector is DESCA:
8667*
8668* NOTATION STORED IN EXPLANATION
8669* ---------------- --------------- ------------------------------------
8670* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
8671* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
8672* the NPROW x NPCOL BLACS process grid
8673* A is distributed over. The context
8674* itself is global, but the handle
8675* (the integer value) may vary.
8676* M_A (global) DESCA( M_ ) The number of rows in the distribu-
8677* ted matrix A, M_A >= 0.
8678* N_A (global) DESCA( N_ ) The number of columns in the distri-
8679* buted matrix A, N_A >= 0.
8680* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
8681* block of the matrix A, IMB_A > 0.
8682* INB_A (global) DESCA( INB_ ) The number of columns of the upper
8683* left block of the matrix A,
8684* INB_A > 0.
8685* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
8686* bute the last M_A-IMB_A rows of A,
8687* MB_A > 0.
8688* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
8689* bute the last N_A-INB_A columns of
8690* A, NB_A > 0.
8691* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
8692* row of the matrix A is distributed,
8693* NPROW > RSRC_A >= 0.
8694* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
8695* first column of A is distributed.
8696* NPCOL > CSRC_A >= 0.
8697* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
8698* array storing the local blocks of
8699* the distributed matrix A,
8700* IF( Lc( 1, N_A ) > 0 )
8701* LLD_A >= MAX( 1, Lr( 1, M_A ) )
8702* ELSE
8703* LLD_A >= 1.
8704*
8705* Let K be the number of rows of a matrix A starting at the global in-
8706* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
8707* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
8708* receive if these K rows were distributed over NPROW processes. If K
8709* is the number of columns of a matrix A starting at the global index
8710* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
8711* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
8712* these K columns were distributed over NPCOL processes.
8713*
8714* The values of Lr() and Lc() may be determined via a call to the func-
8715* tion PB_NUMROC:
8716* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
8717* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
8718*
8719* Arguments
8720* =========
8721*
8722* M (global input) INTEGER
8723* On entry, M specifies the number of rows of the submatrix
8724* sub( A ). M must be at least zero.
8725*
8726* N (global input) INTEGER
8727* On entry, N specifies the number of columns of the submatrix
8728* sub( A ). N must be at least zero.
8729*
8730* A (local input) DOUBLE PRECISION array
8731* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
8732* at least Lc( 1, JA+N-1 ). Before entry, this array contains
8733* the local entries of the matrix A.
8734*
8735* IA (global input) INTEGER
8736* On entry, IA specifies A's global row index, which points to
8737* the beginning of the submatrix sub( A ).
8738*
8739* JA (global input) INTEGER
8740* On entry, JA specifies A's global column index, which points
8741* to the beginning of the submatrix sub( A ).
8742*
8743* DESCA (global and local input) INTEGER array
8744* On entry, DESCA is an integer array of dimension DLEN_. This
8745* is the array descriptor for the matrix A.
8746*
8747* IRPRNT (global input) INTEGER
8748* On entry, IRPRNT specifies the row index of the printing pro-
8749* cess.
8750*
8751* ICPRNT (global input) INTEGER
8752* On entry, ICPRNT specifies the column index of the printing
8753* process.
8754*
8755* CMATNM (global input) CHARACTER*(*)
8756* On entry, CMATNM is the name of the matrix to be printed.
8757*
8758* NOUT (global input) INTEGER
8759* On entry, NOUT specifies the output unit number. When NOUT is
8760* equal to 6, the submatrix is printed on the screen.
8761*
8762* WORK (local workspace) DOUBLE PRECISION array
8763* On entry, WORK is a work array of dimension at least equal to
8764* MAX( IMB_A, MB_A ).
8765*
8766* -- Written on April 1, 1998 by
8767* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
8768*
8769* =====================================================================
8770*
8771* .. Parameters ..
8772 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
8773 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
8774 $ RSRC_
8775 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
8776 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
8777 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
8778 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
8779* ..
8780* .. Local Scalars ..
8781 INTEGER MYCOL, MYROW, NPCOL, NPROW, PCOL, PROW
8782* ..
8783* .. Local Arrays ..
8784 INTEGER DESCA2( DLEN_ )
8785* ..
8786* .. External Subroutines ..
8787 EXTERNAL blacs_gridinfo, pb_desctrans, pb_pdlaprn2
8788* ..
8789* .. Executable Statements ..
8790*
8791* Quick return if possible
8792*
8793 IF( ( m.LE.0 ).OR.( n.LE.0 ) )
8794 $ RETURN
8795*
8796* Convert descriptor
8797*
8798 CALL pb_desctrans( desca, desca2 )
8799*
8800 CALL blacs_gridinfo( desca2( ctxt_ ), nprow, npcol, myrow, mycol )
8801*
8802 IF( desca2( rsrc_ ).GE.0 ) THEN
8803 IF( desca2( csrc_ ).GE.0 ) THEN
8804 CALL pb_pdlaprn2( m, n, a, ia, ja, desca2, irprnt, icprnt,
8805 $ cmatnm, nout, desca2( rsrc_ ),
8806 $ desca2( csrc_ ), work )
8807 ELSE
8808 DO 10 pcol = 0, npcol - 1
8809 IF( ( myrow.EQ.irprnt ).AND.( mycol.EQ.icprnt ) )
8810 $ WRITE( nout, * ) 'Colum-replicated array -- ' ,
8811 $ 'copy in process column: ', pcol
8812 CALL pb_pdlaprn2( m, n, a, ia, ja, desca2, irprnt,
8813 $ icprnt, cmatnm, nout, desca2( rsrc_ ),
8814 $ pcol, work )
8815 10 CONTINUE
8816 END IF
8817 ELSE
8818 IF( desca2( csrc_ ).GE.0 ) THEN
8819 DO 20 prow = 0, nprow - 1
8820 IF( ( myrow.EQ.irprnt ).AND.( mycol.EQ.icprnt ) )
8821 $ WRITE( nout, * ) 'Row-replicated array -- ' ,
8822 $ 'copy in process row: ', prow
8823 CALL pb_pdlaprn2( m, n, a, ia, ja, desca2, irprnt,
8824 $ icprnt, cmatnm, nout, prow,
8825 $ desca2( csrc_ ), work )
8826 20 CONTINUE
8827 ELSE
8828 DO 40 prow = 0, nprow - 1
8829 DO 30 pcol = 0, npcol - 1
8830 IF( ( myrow.EQ.irprnt ).AND.( mycol.EQ.icprnt ) )
8831 $ WRITE( nout, * ) 'Replicated array -- ' ,
8832 $ 'copy in process (', prow, ',', pcol, ')'
8833 CALL pb_pdlaprn2( m, n, a, ia, ja, desca2, irprnt,
8834 $ icprnt, cmatnm, nout, prow, pcol,
8835 $ work )
8836 30 CONTINUE
8837 40 CONTINUE
8838 END IF
8839 END IF
8840*
8841 RETURN
8842*
8843* End of PB_PDLAPRNT
8844*
subroutine pb_desctrans(descin, descout)
Definition pblastst.f:2964
subroutine pb_pdlaprn2(m, n, a, ia, ja, desca, irprnt, icprnt, cmatnm, nout, prow, pcol, work)
Definition pdblastst.f:8848
Here is the caller graph for this function: