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

◆ pcladom()

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

Definition at line 8893 of file pcblastst.f.

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