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

◆ pslagen()

subroutine pslagen ( logical  inplace,
character*1  aform,
character*1  diag,
integer  offa,
integer  m,
integer  n,
integer  ia,
integer  ja,
integer, dimension( * )  desca,
integer  iaseed,
real, dimension( lda, * )  a,
integer  lda 
)

Definition at line 7844 of file psblastst.f.

7846*
7847* -- PBLAS test routine (version 2.0) --
7848* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
7849* and University of California, Berkeley.
7850* April 1, 1998
7851*
7852* .. Scalar Arguments ..
7853 LOGICAL INPLACE
7854 CHARACTER*1 AFORM, DIAG
7855 INTEGER IA, IASEED, JA, LDA, M, N, OFFA
7856* ..
7857* .. Array Arguments ..
7858 INTEGER DESCA( * )
7859 REAL A( LDA, * )
7860* ..
7861*
7862* Purpose
7863* =======
7864*
7865* PSLAGEN generates (or regenerates) a submatrix sub( A ) denoting
7866* A(IA:IA+M-1,JA:JA+N-1).
7867*
7868* Notes
7869* =====
7870*
7871* A description vector is associated with each 2D block-cyclicly dis-
7872* tributed matrix. This vector stores the information required to
7873* establish the mapping between a matrix entry and its corresponding
7874* process and memory location.
7875*
7876* In the following comments, the character _ should be read as
7877* "of the distributed matrix". Let A be a generic term for any 2D
7878* block cyclicly distributed matrix. Its description vector is DESCA:
7879*
7880* NOTATION STORED IN EXPLANATION
7881* ---------------- --------------- ------------------------------------
7882* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
7883* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
7884* the NPROW x NPCOL BLACS process grid
7885* A is distributed over. The context
7886* itself is global, but the handle
7887* (the integer value) may vary.
7888* M_A (global) DESCA( M_ ) The number of rows in the distribu-
7889* ted matrix A, M_A >= 0.
7890* N_A (global) DESCA( N_ ) The number of columns in the distri-
7891* buted matrix A, N_A >= 0.
7892* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
7893* block of the matrix A, IMB_A > 0.
7894* INB_A (global) DESCA( INB_ ) The number of columns of the upper
7895* left block of the matrix A,
7896* INB_A > 0.
7897* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
7898* bute the last M_A-IMB_A rows of A,
7899* MB_A > 0.
7900* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
7901* bute the last N_A-INB_A columns of
7902* A, NB_A > 0.
7903* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
7904* row of the matrix A is distributed,
7905* NPROW > RSRC_A >= 0.
7906* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
7907* first column of A is distributed.
7908* NPCOL > CSRC_A >= 0.
7909* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
7910* array storing the local blocks of
7911* the distributed matrix A,
7912* IF( Lc( 1, N_A ) > 0 )
7913* LLD_A >= MAX( 1, Lr( 1, M_A ) )
7914* ELSE
7915* LLD_A >= 1.
7916*
7917* Let K be the number of rows of a matrix A starting at the global in-
7918* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
7919* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
7920* receive if these K rows were distributed over NPROW processes. If K
7921* is the number of columns of a matrix A starting at the global index
7922* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
7923* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
7924* these K columns were distributed over NPCOL processes.
7925*
7926* The values of Lr() and Lc() may be determined via a call to the func-
7927* tion PB_NUMROC:
7928* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
7929* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
7930*
7931* Arguments
7932* =========
7933*
7934* INPLACE (global input) LOGICAL
7935* On entry, INPLACE specifies if the matrix should be generated
7936* in place or not. If INPLACE is .TRUE., the local random array
7937* to be generated will start in memory at the local memory lo-
7938* cation A( 1, 1 ), otherwise it will start at the local posi-
7939* tion induced by IA and JA.
7940*
7941* AFORM (global input) CHARACTER*1
7942* On entry, AFORM specifies the type of submatrix to be genera-
7943* ted as follows:
7944* AFORM = 'S', sub( A ) is a symmetric matrix,
7945* AFORM = 'H', sub( A ) is a Hermitian matrix,
7946* AFORM = 'T', sub( A ) is overrwritten with the transpose
7947* of what would normally be generated,
7948* AFORM = 'C', sub( A ) is overwritten with the conjugate
7949* transpose of what would normally be genera-
7950* ted.
7951* AFORM = 'N', a random submatrix is generated.
7952*
7953* DIAG (global input) CHARACTER*1
7954* On entry, DIAG specifies if the generated submatrix is diago-
7955* nally dominant or not as follows:
7956* DIAG = 'D' : sub( A ) is diagonally dominant,
7957* DIAG = 'N' : sub( A ) is not diagonally dominant.
7958*
7959* OFFA (global input) INTEGER
7960* On entry, OFFA specifies the offdiagonal of the underlying
7961* matrix A(1:DESCA(M_),1:DESCA(N_)) of interest when the subma-
7962* trix is symmetric, Hermitian or diagonally dominant. OFFA = 0
7963* specifies the main diagonal, OFFA > 0 specifies a subdiago-
7964* nal, and OFFA < 0 specifies a superdiagonal (see further de-
7965* tails).
7966*
7967* M (global input) INTEGER
7968* On entry, M specifies the global number of matrix rows of the
7969* submatrix sub( A ) to be generated. M must be at least zero.
7970*
7971* N (global input) INTEGER
7972* On entry, N specifies the global number of matrix columns of
7973* the submatrix sub( A ) to be generated. N must be at least
7974* zero.
7975*
7976* IA (global input) INTEGER
7977* On entry, IA specifies A's global row index, which points to
7978* the beginning of the submatrix sub( A ).
7979*
7980* JA (global input) INTEGER
7981* On entry, JA specifies A's global column index, which points
7982* to the beginning of the submatrix sub( A ).
7983*
7984* DESCA (global and local input) INTEGER array
7985* On entry, DESCA is an integer array of dimension DLEN_. This
7986* is the array descriptor for the matrix A.
7987*
7988* IASEED (global input) INTEGER
7989* On entry, IASEED specifies the seed number to generate the
7990* matrix A. IASEED must be at least zero.
7991*
7992* A (local output) REAL array
7993* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
7994* at least Lc( 1, JA+N-1 ). On exit, this array contains the
7995* local entries of the randomly generated submatrix sub( A ).
7996*
7997* LDA (local input) INTEGER
7998* On entry, LDA specifies the local leading dimension of the
7999* array A. When INPLACE is .FALSE., LDA is usually DESCA(LLD_).
8000* This restriction is however not enforced, and this subroutine
8001* requires only that LDA >= MAX( 1, Mp ) where
8002*
8003* Mp = PB_NUMROC( M, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW ).
8004*
8005* PB_NUMROC is a ScaLAPACK tool function; MYROW, MYCOL, NPROW
8006* and NPCOL can be determined by calling the BLACS subroutine
8007* BLACS_GRIDINFO.
8008*
8009* Further Details
8010* ===============
8011*
8012* OFFD is tied to the matrix described by DESCA, as opposed to the
8013* piece that is currently (re)generated. This is a global information
8014* independent from the distribution parameters. Below are examples of
8015* the meaning of OFFD for a global 7 by 5 matrix:
8016*
8017* ---------------------------------------------------------------------
8018* OFFD | 0 -1 -2 -3 -4 0 -1 -2 -3 -4 0 -1 -2 -3 -4
8019* -------|-------------------------------------------------------------
8020* | | OFFD=-1 | OFFD=0 OFFD=2
8021* | V V
8022* 0 | . d . . . -> d . . . . . . . . .
8023* 1 | . . d . . . d . . . . . . . .
8024* 2 | . . . d . . . d . . -> d . . . .
8025* 3 | . . . . d . . . d . . d . . .
8026* 4 | . . . . . . . . . d . . d . .
8027* 5 | . . . . . . . . . . . . . d .
8028* 6 | . . . . . . . . . . . . . . d
8029* ---------------------------------------------------------------------
8030*
8031* -- Written on April 1, 1998 by
8032* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
8033*
8034* =====================================================================
8035*
8036* .. Parameters ..
8037 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
8038 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
8039 $ RSRC_
8040 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
8041 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
8042 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
8043 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
8044 INTEGER JMP_1, JMP_COL, JMP_IMBV, JMP_INBV, JMP_LEN,
8045 $ JMP_MB, JMP_NB, JMP_NPIMBLOC, JMP_NPMB,
8046 $ JMP_NQINBLOC, JMP_NQNB, JMP_ROW
8047 parameter( jmp_1 = 1, jmp_row = 2, jmp_col = 3,
8048 $ jmp_mb = 4, jmp_imbv = 5, jmp_npmb = 6,
8049 $ jmp_npimbloc = 7, jmp_nb = 8, jmp_inbv = 9,
8050 $ jmp_nqnb = 10, jmp_nqinbloc = 11,
8051 $ jmp_len = 11 )
8052* ..
8053* .. Local Scalars ..
8054 LOGICAL DIAGDO, SYMM, HERM, NOTRAN
8055 INTEGER CSRC, I, IACOL, IAROW, ICTXT, IIA, ILOCBLK,
8056 $ ILOCOFF, ILOW, IMB, IMB1, IMBLOC, IMBVIR, INB,
8057 $ INB1, INBLOC, INBVIR, INFO, IOFFDA, ITMP, IUPP,
8058 $ IVIR, JJA, JLOCBLK, JLOCOFF, JVIR, LCMT00,
8059 $ LMBLOC, LNBLOC, LOW, MAXMN, MB, MBLKS, MP,
8060 $ MRCOL, MRROW, MYCDIST, MYCOL, MYRDIST, MYROW,
8061 $ NB, NBLKS, NPCOL, NPROW, NQ, NVIR, RSRC, UPP
8062 REAL ALPHA
8063* ..
8064* .. Local Arrays ..
8065 INTEGER DESCA2( DLEN_ ), IMULADD( 4, JMP_LEN ),
8066 $ IRAN( 2 ), JMP( JMP_LEN ), MULADD0( 4 )
8067* ..
8068* .. External Subroutines ..
8069 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
8073 $ pxerbla
8074* ..
8075* .. External Functions ..
8076 LOGICAL LSAME
8077 EXTERNAL lsame
8078* ..
8079* .. Intrinsic Functions ..
8080 INTRINSIC max, min, real
8081* ..
8082* .. Data Statements ..
8083 DATA ( muladd0( i ), i = 1, 4 ) / 20077, 16838,
8084 $ 12345, 0 /
8085* ..
8086* .. Executable Statements ..
8087*
8088* Convert descriptor
8089*
8090 CALL pb_desctrans( desca, desca2 )
8091*
8092* Test the input arguments
8093*
8094 ictxt = desca2( ctxt_ )
8095 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
8096*
8097* Test the input parameters
8098*
8099 info = 0
8100 IF( nprow.EQ.-1 ) THEN
8101 info = -( 1000 + ctxt_ )
8102 ELSE
8103 symm = lsame( aform, 'S' )
8104 herm = lsame( aform, 'H' )
8105 notran = lsame( aform, 'N' )
8106 diagdo = lsame( diag, 'D' )
8107 IF( .NOT.( symm.OR.herm.OR.notran ) .AND.
8108 $ .NOT.( lsame( aform, 'T' ) ) .AND.
8109 $ .NOT.( lsame( aform, 'C' ) ) ) THEN
8110 info = -2
8111 ELSE IF( ( .NOT.diagdo ) .AND.
8112 $ ( .NOT.lsame( diag, 'N' ) ) ) THEN
8113 info = -3
8114 END IF
8115 CALL pb_chkmat( ictxt, m, 5, n, 6, ia, ja, desca2, 10, info )
8116 END IF
8117*
8118 IF( info.NE.0 ) THEN
8119 CALL pxerbla( ictxt, 'PSLAGEN', -info )
8120 RETURN
8121 END IF
8122*
8123* Quick return if possible
8124*
8125 IF( ( m.LE.0 ).OR.( n.LE.0 ) )
8126 $ RETURN
8127*
8128* Start the operations
8129*
8130 mb = desca2( mb_ )
8131 nb = desca2( nb_ )
8132 imb = desca2( imb_ )
8133 inb = desca2( inb_ )
8134 rsrc = desca2( rsrc_ )
8135 csrc = desca2( csrc_ )
8136*
8137* Figure out local information about the distributed matrix operand
8138*
8139 CALL pb_ainfog2l( m, n, ia, ja, desca2, nprow, npcol, myrow,
8140 $ mycol, imb1, inb1, mp, nq, iia, jja, iarow,
8141 $ iacol, mrrow, mrcol )
8142*
8143* Decide where the entries shall be stored in memory
8144*
8145 IF( inplace ) THEN
8146 iia = 1
8147 jja = 1
8148 END IF
8149*
8150* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC, LNBLOC,
8151* ILOW, LOW, IUPP, and UPP.
8152*
8153 ioffda = ja + offa - ia
8154 CALL pb_binfo( ioffda, mp, nq, imb1, inb1, mb, nb, mrrow,
8155 $ mrcol, lcmt00, mblks, nblks, imbloc, inbloc,
8156 $ lmbloc, lnbloc, ilow, low, iupp, upp )
8157*
8158* Initialize ILOCBLK, ILOCOFF, MYRDIST, JLOCBLK, JLOCOFF, MYCDIST
8159* This values correspond to the square virtual underlying matrix
8160* of size MAX( M_ + MAX( 0, -OFFA ), N_ + MAX( 0, OFFA ) ) used
8161* to set up the random sequence. For practical purposes, the size
8162* of this virtual matrix is upper bounded by M_ + N_ - 1.
8163*
8164 itmp = max( 0, -offa )
8165 ivir = ia + itmp
8166 imbvir = imb + itmp
8167 nvir = desca2( m_ ) + itmp
8168*
8169 CALL pb_locinfo( ivir, imbvir, mb, myrow, rsrc, nprow, ilocblk,
8170 $ ilocoff, myrdist )
8171*
8172 itmp = max( 0, offa )
8173 jvir = ja + itmp
8174 inbvir = inb + itmp
8175 nvir = max( max( nvir, desca2( n_ ) + itmp ),
8176 $ desca2( m_ ) + desca2( n_ ) - 1 )
8177*
8178 CALL pb_locinfo( jvir, inbvir, nb, mycol, csrc, npcol, jlocblk,
8179 $ jlocoff, mycdist )
8180*
8181 IF( symm .OR. herm .OR. notran ) THEN
8182*
8183 CALL pb_initjmp( .true., nvir, imbvir, inbvir, imbloc, inbloc,
8184 $ mb, nb, rsrc, csrc, nprow, npcol, 1, jmp )
8185*
8186* Compute constants to jump JMP( * ) numbers in the sequence
8187*
8188 CALL pb_initmuladd( muladd0, jmp, imuladd )
8189*
8190* Compute and set the random value corresponding to A( IA, JA )
8191*
8192 CALL pb_setlocran( iaseed, ilocblk, jlocblk, ilocoff, jlocoff,
8193 $ myrdist, mycdist, nprow, npcol, jmp,
8194 $ imuladd, iran )
8195*
8196 CALL pb_slagen( 'Lower', aform, a( iia, jja ), lda, lcmt00,
8197 $ iran, mblks, imbloc, mb, lmbloc, nblks, inbloc,
8198 $ nb, lnbloc, jmp, imuladd )
8199*
8200 END IF
8201*
8202 IF( symm .OR. herm .OR. ( .NOT. notran ) ) THEN
8203*
8204 CALL pb_initjmp( .false., nvir, imbvir, inbvir, imbloc, inbloc,
8205 $ mb, nb, rsrc, csrc, nprow, npcol, 1, jmp )
8206*
8207* Compute constants to jump JMP( * ) numbers in the sequence
8208*
8209 CALL pb_initmuladd( muladd0, jmp, imuladd )
8210*
8211* Compute and set the random value corresponding to A( IA, JA )
8212*
8213 CALL pb_setlocran( iaseed, ilocblk, jlocblk, ilocoff, jlocoff,
8214 $ myrdist, mycdist, nprow, npcol, jmp,
8215 $ imuladd, iran )
8216*
8217 CALL pb_slagen( 'Upper', aform, a( iia, jja ), lda, lcmt00,
8218 $ iran, mblks, imbloc, mb, lmbloc, nblks, inbloc,
8219 $ nb, lnbloc, jmp, imuladd )
8220*
8221 END IF
8222*
8223 IF( diagdo ) THEN
8224*
8225 maxmn = max( desca2( m_ ), desca2( n_ ) )
8226 alpha = real( maxmn )
8227*
8228 IF( ioffda.GE.0 ) THEN
8229 CALL psladom( inplace, min( max( 0, m-ioffda ), n ), alpha,
8230 $ a, min( ia+ioffda, ia+m-1 ), ja, desca )
8231 ELSE
8232 CALL psladom( inplace, min( m, max( 0, n+ioffda ) ), alpha,
8233 $ a, ia, min( ja-ioffda, ja+n-1 ), desca )
8234 END IF
8235*
8236 END IF
8237*
8238 RETURN
8239*
8240* End of PSLAGEN
8241*
subroutine pb_ainfog2l(m, n, i, j, desc, nprow, npcol, myrow, mycol, imb1, inb1, mp, nq, ii, jj, prow, pcol, rprow, rpcol)
Definition pblastst.f:2023
subroutine pb_binfo(offd, m, n, imb1, inb1, mb, nb, mrrow, mrcol, lcmt00, mblks, nblks, imbloc, inbloc, lmbloc, lnbloc, ilow, low, iupp, upp)
Definition pblastst.f:3577
subroutine pb_setran(iran, iac)
Definition pblastst.f:4759
subroutine pb_locinfo(i, inb, nb, myroc, srcproc, nprocs, ilocblk, ilocoff, mydist)
Definition pblastst.f:3910
subroutine pb_chkmat(ictxt, m, mpos0, n, npos0, ia, ja, desca, dpos0, info)
Definition pblastst.f:2742
subroutine pb_jump(k, muladd, irann, iranm, ima)
Definition pblastst.f:4648
subroutine pb_setlocran(seed, ilocblk, jlocblk, ilocoff, jlocoff, myrdist, mycdist, nprow, npcol, jmp, imuladd, iran)
Definition pblastst.f:4302
subroutine pb_initmuladd(muladd0, jmp, imuladd)
Definition pblastst.f:4196
subroutine pb_desctrans(descin, descout)
Definition pblastst.f:2964
subroutine pb_initjmp(colmaj, nvir, imbvir, inbvir, imbloc, inbloc, mb, nb, rsrc, csrc, nprow, npcol, stride, jmp)
Definition pblastst.f:4045
subroutine pb_jumpit(muladd, irann, iranm)
Definition pblastst.f:4822
#define max(A, B)
Definition pcgemr.c:180
#define min(A, B)
Definition pcgemr.c:181
subroutine psladom(inplace, n, alpha, a, ia, ja, desca)
Definition psblastst.f:8244
subroutine pb_slagen(uplo, aform, a, lda, lcmt00, iran, mblks, imbloc, mb, lmbloc, nblks, inbloc, nb, lnbloc, jmp, imuladd)
Definition psblastst.f:9739
subroutine pxerbla(ictxt, srname, info)
Definition pxerbla.f:2
logical function lsame(ca, cb)
Definition tools.f:1724
Here is the call graph for this function:
Here is the caller graph for this function: