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

◆ pzladom()

subroutine pzladom ( logical  inplace,
integer  n,
complex*16  alpha,
complex*16, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 8895 of file pzblastst.f.

8896*
8897* -- PBLAS test routine (version 2.0) --
8898* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
8899* and University of California, Berkeley.
8900* April 1, 1998
8901*
8902* .. Scalar Arguments ..
8903 LOGICAL INPLACE
8904 INTEGER IA, JA, N
8905 COMPLEX*16 ALPHA
8906* ..
8907* .. Array Arguments ..
8908 INTEGER DESCA( * )
8909 COMPLEX*16 A( * )
8910* ..
8911*
8912* Purpose
8913* =======
8914*
8915* PZLADOM adds alpha to the diagonal entries of an n by n submatrix
8916* sub( A ) denoting A( IA:IA+N-1, JA:JA+N-1 ).
8917*
8918* Notes
8919* =====
8920*
8921* A description vector is associated with each 2D block-cyclicly dis-
8922* tributed matrix. This vector stores the information required to
8923* establish the mapping between a matrix entry and its corresponding
8924* process and memory location.
8925*
8926* In the following comments, the character _ should be read as
8927* "of the distributed matrix". Let A be a generic term for any 2D
8928* block cyclicly distributed matrix. Its description vector is DESCA:
8929*
8930* NOTATION STORED IN EXPLANATION
8931* ---------------- --------------- ------------------------------------
8932* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
8933* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
8934* the NPROW x NPCOL BLACS process grid
8935* A is distributed over. The context
8936* itself is global, but the handle
8937* (the integer value) may vary.
8938* M_A (global) DESCA( M_ ) The number of rows in the distribu-
8939* ted matrix A, M_A >= 0.
8940* N_A (global) DESCA( N_ ) The number of columns in the distri-
8941* buted matrix A, N_A >= 0.
8942* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
8943* block of the matrix A, IMB_A > 0.
8944* INB_A (global) DESCA( INB_ ) The number of columns of the upper
8945* left block of the matrix A,
8946* INB_A > 0.
8947* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
8948* bute the last M_A-IMB_A rows of A,
8949* MB_A > 0.
8950* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
8951* bute the last N_A-INB_A columns of
8952* A, NB_A > 0.
8953* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
8954* row of the matrix A is distributed,
8955* NPROW > RSRC_A >= 0.
8956* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
8957* first column of A is distributed.
8958* NPCOL > CSRC_A >= 0.
8959* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
8960* array storing the local blocks of
8961* the distributed matrix A,
8962* IF( Lc( 1, N_A ) > 0 )
8963* LLD_A >= MAX( 1, Lr( 1, M_A ) )
8964* ELSE
8965* LLD_A >= 1.
8966*
8967* Let K be the number of rows of a matrix A starting at the global in-
8968* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
8969* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
8970* receive if these K rows were distributed over NPROW processes. If K
8971* is the number of columns of a matrix A starting at the global index
8972* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
8973* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
8974* these K columns were distributed over NPCOL processes.
8975*
8976* The values of Lr() and Lc() may be determined via a call to the func-
8977* tion PB_NUMROC:
8978* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
8979* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
8980*
8981* Arguments
8982* =========
8983*
8984* INPLACE (global input) LOGICAL
8985* On entry, INPLACE specifies if the matrix should be generated
8986* in place or not. If INPLACE is .TRUE., the local random array
8987* to be generated will start in memory at the local memory lo-
8988* cation A( 1, 1 ), otherwise it will start at the local posi-
8989* tion induced by IA and JA.
8990*
8991* N (global input) INTEGER
8992* On entry, N specifies the global order of the submatrix
8993* sub( A ) to be modified. N must be at least zero.
8994*
8995* ALPHA (global input) COMPLEX*16
8996* On entry, ALPHA specifies the scalar alpha.
8997*
8998* A (local input/local output) COMPLEX*16 array
8999* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
9000* at least Lc( 1, JA+N-1 ). Before entry, this array contains
9001* the local entries of the matrix A. On exit, the local entries
9002* of this array corresponding to the main diagonal of sub( A )
9003* have been updated.
9004*
9005* IA (global input) INTEGER
9006* On entry, IA specifies A's global row index, which points to
9007* the beginning of the submatrix sub( A ).
9008*
9009* JA (global input) INTEGER
9010* On entry, JA specifies A's global column index, which points
9011* to the beginning of the submatrix sub( A ).
9012*
9013* DESCA (global and local input) INTEGER array
9014* On entry, DESCA is an integer array of dimension DLEN_. This
9015* is the array descriptor for the matrix A.
9016*
9017* -- Written on April 1, 1998 by
9018* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
9019*
9020* =====================================================================
9021*
9022* .. Parameters ..
9023 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
9024 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
9025 $ RSRC_
9026 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
9027 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
9028 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
9029 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
9030* ..
9031* .. Local Scalars ..
9032 LOGICAL GODOWN, GOLEFT
9033 INTEGER I, IACOL, IAROW, ICTXT, IIA, IJOFFA, ILOW,
9034 $ IMB1, IMBLOC, INB1, INBLOC, IOFFA, IOFFD, IUPP,
9035 $ JJA, JOFFA, JOFFD, LCMT, LCMT00, LDA, LDAP1,
9036 $ LMBLOC, LNBLOC, LOW, MB, MBLKD, MBLKS, MBLOC,
9037 $ MRCOL, MRROW, MYCOL, MYROW, NB, NBLKD, NBLKS,
9038 $ NBLOC, NP, NPCOL, NPROW, NQ, PMB, QNB, UPP
9039 COMPLEX*16 ATMP
9040* ..
9041* .. Local Scalars ..
9042 INTEGER DESCA2( DLEN_ )
9043* ..
9044* .. External Subroutines ..
9045 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
9046 $ pb_desctrans
9047* ..
9048* .. Intrinsic Functions ..
9049 INTRINSIC abs, dble, dcmplx, dimag, max, min
9050* ..
9051* .. Executable Statements ..
9052*
9053* Convert descriptor
9054*
9055 CALL pb_desctrans( desca, desca2 )
9056*
9057* Get grid parameters
9058*
9059 ictxt = desca2( ctxt_ )
9060 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
9061*
9062 IF( n.EQ.0 )
9063 $ RETURN
9064*
9065 CALL pb_ainfog2l( n, n, ia, ja, desca2, nprow, npcol, myrow,
9066 $ mycol, imb1, inb1, np, nq, iia, jja, iarow,
9067 $ iacol, mrrow, mrcol )
9068*
9069* Decide where the entries shall be stored in memory
9070*
9071 IF( inplace ) THEN
9072 iia = 1
9073 jja = 1
9074 END IF
9075*
9076* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC, LNBLOC,
9077* ILOW, LOW, IUPP, and UPP.
9078*
9079 mb = desca2( mb_ )
9080 nb = desca2( nb_ )
9081*
9082 CALL pb_binfo( 0, np, nq, imb1, inb1, mb, nb, mrrow, mrcol,
9083 $ lcmt00, mblks, nblks, imbloc, inbloc, lmbloc,
9084 $ lnbloc, ilow, low, iupp, upp )
9085*
9086 ioffa = iia - 1
9087 joffa = jja - 1
9088 lda = desca2( lld_ )
9089 ldap1 = lda + 1
9090*
9091 IF( desca2( rsrc_ ).LT.0 ) THEN
9092 pmb = mb
9093 ELSE
9094 pmb = nprow * mb
9095 END IF
9096 IF( desca2( csrc_ ).LT.0 ) THEN
9097 qnb = nb
9098 ELSE
9099 qnb = npcol * nb
9100 END IF
9101*
9102* Handle the first block of rows or columns separately, and update
9103* LCMT00, MBLKS and NBLKS.
9104*
9105 godown = ( lcmt00.GT.iupp )
9106 goleft = ( lcmt00.LT.ilow )
9107*
9108 IF( .NOT.godown .AND. .NOT.goleft ) THEN
9109*
9110* LCMT00 >= ILOW && LCMT00 <= IUPP
9111*
9112 IF( lcmt00.GE.0 ) THEN
9113 ijoffa = ioffa+lcmt00 + ( joffa - 1 ) * lda
9114 DO 10 i = 1, min( inbloc, max( 0, imbloc - lcmt00 ) )
9115 atmp = a( ijoffa + i*ldap1 )
9116 a( ijoffa + i*ldap1 ) = alpha +
9117 $ dcmplx( abs( dble( atmp ) ),
9118 $ abs( dimag( atmp ) ) )
9119 10 CONTINUE
9120 ELSE
9121 ijoffa = ioffa + ( joffa - lcmt00 - 1 ) * lda
9122 DO 20 i = 1, min( imbloc, max( 0, inbloc + lcmt00 ) )
9123 atmp = a( ijoffa + i*ldap1 )
9124 a( ijoffa + i*ldap1 ) = alpha +
9125 $ dcmplx( abs( dble( atmp ) ),
9126 $ abs( dimag( atmp ) ) )
9127 20 CONTINUE
9128 END IF
9129 goleft = ( ( lcmt00 - ( iupp - upp + pmb ) ).LT.ilow )
9130 godown = .NOT.goleft
9131*
9132 END IF
9133*
9134 IF( godown ) THEN
9135*
9136 lcmt00 = lcmt00 - ( iupp - upp + pmb )
9137 mblks = mblks - 1
9138 ioffa = ioffa + imbloc
9139*
9140 30 CONTINUE
9141 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
9142 lcmt00 = lcmt00 - pmb
9143 mblks = mblks - 1
9144 ioffa = ioffa + mb
9145 GO TO 30
9146 END IF
9147*
9148 lcmt = lcmt00
9149 mblkd = mblks
9150 ioffd = ioffa
9151*
9152 mbloc = mb
9153 40 CONTINUE
9154 IF( mblkd.GT.0 .AND. lcmt.GE.ilow ) THEN
9155 IF( mblkd.EQ.1 )
9156 $ mbloc = lmbloc
9157 IF( lcmt.GE.0 ) THEN
9158 ijoffa = ioffd + lcmt + ( joffa - 1 ) * lda
9159 DO 50 i = 1, min( inbloc, max( 0, mbloc - lcmt ) )
9160 atmp = a( ijoffa + i*ldap1 )
9161 a( ijoffa + i*ldap1 ) = alpha +
9162 $ dcmplx( abs( dble( atmp ) ),
9163 $ abs( dimag( atmp ) ) )
9164 50 CONTINUE
9165 ELSE
9166 ijoffa = ioffd + ( joffa - lcmt - 1 ) * lda
9167 DO 60 i = 1, min( mbloc, max( 0, inbloc + lcmt ) )
9168 atmp = a( ijoffa + i*ldap1 )
9169 a( ijoffa + i*ldap1 ) = alpha +
9170 $ dcmplx( abs( dble( atmp ) ),
9171 $ abs( dimag( atmp ) ) )
9172 60 CONTINUE
9173 END IF
9174 lcmt00 = lcmt
9175 lcmt = lcmt - pmb
9176 mblks = mblkd
9177 mblkd = mblkd - 1
9178 ioffa = ioffd
9179 ioffd = ioffd + mbloc
9180 GO TO 40
9181 END IF
9182*
9183 lcmt00 = lcmt00 + low - ilow + qnb
9184 nblks = nblks - 1
9185 joffa = joffa + inbloc
9186*
9187 ELSE IF( goleft ) THEN
9188*
9189 lcmt00 = lcmt00 + low - ilow + qnb
9190 nblks = nblks - 1
9191 joffa = joffa + inbloc
9192*
9193 70 CONTINUE
9194 IF( nblks.GT.0 .AND. lcmt00.LT.low ) THEN
9195 lcmt00 = lcmt00 + qnb
9196 nblks = nblks - 1
9197 joffa = joffa + nb
9198 GO TO 70
9199 END IF
9200*
9201 lcmt = lcmt00
9202 nblkd = nblks
9203 joffd = joffa
9204*
9205 nbloc = nb
9206 80 CONTINUE
9207 IF( nblkd.GT.0 .AND. lcmt.LE.iupp ) THEN
9208 IF( nblkd.EQ.1 )
9209 $ nbloc = lnbloc
9210 IF( lcmt.GE.0 ) THEN
9211 ijoffa = ioffa + lcmt + ( joffd - 1 ) * lda
9212 DO 90 i = 1, min( nbloc, max( 0, imbloc - lcmt ) )
9213 atmp = a( ijoffa + i*ldap1 )
9214 a( ijoffa + i*ldap1 ) = alpha +
9215 $ dcmplx( abs( dble( atmp ) ),
9216 $ abs( dimag( atmp ) ) )
9217 90 CONTINUE
9218 ELSE
9219 ijoffa = ioffa + ( joffd - lcmt - 1 ) * lda
9220 DO 100 i = 1, min( imbloc, max( 0, nbloc + lcmt ) )
9221 atmp = a( ijoffa + i*ldap1 )
9222 a( ijoffa + i*ldap1 ) = alpha +
9223 $ dcmplx( abs( dble( atmp ) ),
9224 $ abs( dimag( atmp ) ) )
9225 100 CONTINUE
9226 END IF
9227 lcmt00 = lcmt
9228 lcmt = lcmt + qnb
9229 nblks = nblkd
9230 nblkd = nblkd - 1
9231 joffa = joffd
9232 joffd = joffd + nbloc
9233 GO TO 80
9234 END IF
9235*
9236 lcmt00 = lcmt00 - ( iupp - upp + pmb )
9237 mblks = mblks - 1
9238 ioffa = ioffa + imbloc
9239*
9240 END IF
9241*
9242 nbloc = nb
9243 110 CONTINUE
9244 IF( nblks.GT.0 ) THEN
9245 IF( nblks.EQ.1 )
9246 $ nbloc = lnbloc
9247 120 CONTINUE
9248 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
9249 lcmt00 = lcmt00 - pmb
9250 mblks = mblks - 1
9251 ioffa = ioffa + mb
9252 GO TO 120
9253 END IF
9254*
9255 lcmt = lcmt00
9256 mblkd = mblks
9257 ioffd = ioffa
9258*
9259 mbloc = mb
9260 130 CONTINUE
9261 IF( mblkd.GT.0 .AND. lcmt.GE.low ) THEN
9262 IF( mblkd.EQ.1 )
9263 $ mbloc = lmbloc
9264 IF( lcmt.GE.0 ) THEN
9265 ijoffa = ioffd + lcmt + ( joffa - 1 ) * lda
9266 DO 140 i = 1, min( nbloc, max( 0, mbloc - lcmt ) )
9267 atmp = a( ijoffa + i*ldap1 )
9268 a( ijoffa + i*ldap1 ) = alpha +
9269 $ dcmplx( abs( dble( atmp ) ),
9270 $ abs( dimag( atmp ) ) )
9271 140 CONTINUE
9272 ELSE
9273 ijoffa = ioffd + ( joffa - lcmt - 1 ) * lda
9274 DO 150 i = 1, min( mbloc, max( 0, nbloc + lcmt ) )
9275 atmp = a( ijoffa + i*ldap1 )
9276 a( ijoffa + i*ldap1 ) = alpha +
9277 $ dcmplx( abs( dble( atmp ) ),
9278 $ abs( dimag( atmp ) ) )
9279 150 CONTINUE
9280 END IF
9281 lcmt00 = lcmt
9282 lcmt = lcmt - pmb
9283 mblks = mblkd
9284 mblkd = mblkd - 1
9285 ioffa = ioffd
9286 ioffd = ioffd + mbloc
9287 GO TO 130
9288 END IF
9289*
9290 lcmt00 = lcmt00 + qnb
9291 nblks = nblks - 1
9292 joffa = joffa + nbloc
9293 GO TO 110
9294*
9295 END IF
9296*
9297 RETURN
9298*
9299* End of PZLADOM
9300*
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_desctrans(descin, descout)
Definition pblastst.f:2964
#define max(A, B)
Definition pcgemr.c:180
#define min(A, B)
Definition pcgemr.c:181
Here is the call graph for this function:
Here is the caller graph for this function: