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

◆ pdlagen()

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

Definition at line 7843 of file pdblastst.f.

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