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

◆ pb_pslaprnt()

subroutine pb_pslaprnt ( integer  m,
integer  n,
real, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca,
integer  irprnt,
integer  icprnt,
character*(*)  cmatnm,
integer  nout,
real, dimension( * )  work 
)

Definition at line 8634 of file psblastst.f.

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