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

◆ pcipset()

subroutine pcipset ( character*1  toggle,
integer  n,
complex, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 7043 of file pcblastst.f.

7044*
7045* -- PBLAS test routine (version 2.0) --
7046* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
7047* and University of California, Berkeley.
7048* April 1, 1998
7049*
7050* .. Scalar Arguments ..
7051 CHARACTER*1 TOGGLE
7052 INTEGER IA, JA, N
7053* ..
7054* .. Array Arguments ..
7055 INTEGER DESCA( * )
7056 COMPLEX A( * )
7057* ..
7058*
7059* Purpose
7060* =======
7061*
7062* PCIPSET sets the imaginary part of the diagonal entries of an n by n
7063* matrix sub( A ) denoting A( IA:IA+N-1, JA:JA+N-1 ). This is used to
7064* test the PBLAS routines for complex Hermitian matrices, which are
7065* either not supposed to access or use the imaginary parts of the dia-
7066* gonals, or supposed to set them to zero. The value used to set the
7067* imaginary part of the diagonals depends on the value of TOGGLE.
7068*
7069* Notes
7070* =====
7071*
7072* A description vector is associated with each 2D block-cyclicly dis-
7073* tributed matrix. This vector stores the information required to
7074* establish the mapping between a matrix entry and its corresponding
7075* process and memory location.
7076*
7077* In the following comments, the character _ should be read as
7078* "of the distributed matrix". Let A be a generic term for any 2D
7079* block cyclicly distributed matrix. Its description vector is DESCA:
7080*
7081* NOTATION STORED IN EXPLANATION
7082* ---------------- --------------- ------------------------------------
7083* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
7084* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
7085* the NPROW x NPCOL BLACS process grid
7086* A is distributed over. The context
7087* itself is global, but the handle
7088* (the integer value) may vary.
7089* M_A (global) DESCA( M_ ) The number of rows in the distribu-
7090* ted matrix A, M_A >= 0.
7091* N_A (global) DESCA( N_ ) The number of columns in the distri-
7092* buted matrix A, N_A >= 0.
7093* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
7094* block of the matrix A, IMB_A > 0.
7095* INB_A (global) DESCA( INB_ ) The number of columns of the upper
7096* left block of the matrix A,
7097* INB_A > 0.
7098* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
7099* bute the last M_A-IMB_A rows of A,
7100* MB_A > 0.
7101* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
7102* bute the last N_A-INB_A columns of
7103* A, NB_A > 0.
7104* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
7105* row of the matrix A is distributed,
7106* NPROW > RSRC_A >= 0.
7107* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
7108* first column of A is distributed.
7109* NPCOL > CSRC_A >= 0.
7110* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
7111* array storing the local blocks of
7112* the distributed matrix A,
7113* IF( Lc( 1, N_A ) > 0 )
7114* LLD_A >= MAX( 1, Lr( 1, M_A ) )
7115* ELSE
7116* LLD_A >= 1.
7117*
7118* Let K be the number of rows of a matrix A starting at the global in-
7119* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
7120* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
7121* receive if these K rows were distributed over NPROW processes. If K
7122* is the number of columns of a matrix A starting at the global index
7123* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
7124* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
7125* these K columns were distributed over NPCOL processes.
7126*
7127* The values of Lr() and Lc() may be determined via a call to the func-
7128* tion PB_NUMROC:
7129* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
7130* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
7131*
7132* Arguments
7133* =========
7134*
7135* TOGGLE (global input) CHARACTER*1
7136* On entry, TOGGLE specifies the set-value to be used as fol-
7137* lows:
7138* If TOGGLE = 'Z' or 'z', the imaginary part of the diago-
7139* nals are set to zero,
7140* If TOGGLE = 'B' or 'b', the imaginary part of the diago-
7141* nals are set to a large value.
7142*
7143* N (global input) INTEGER
7144* On entry, N specifies the order of sub( A ). N must be at
7145* least zero.
7146*
7147* A (local input/local output) pointer to COMPLEX
7148* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
7149* at least Lc( 1, JA+N-1 ). Before entry, this array contains
7150* the local entries of the matrix A. On exit, the diagonals of
7151* sub( A ) have been updated as specified by TOGGLE.
7152*
7153* IA (global input) INTEGER
7154* On entry, IA specifies A's global row index, which points to
7155* the beginning of the submatrix sub( A ).
7156*
7157* JA (global input) INTEGER
7158* On entry, JA specifies A's global column index, which points
7159* to the beginning of the submatrix sub( A ).
7160*
7161* DESCA (global and local input) INTEGER array
7162* On entry, DESCA is an integer array of dimension DLEN_. This
7163* is the array descriptor for the matrix A.
7164*
7165* -- Written on April 1, 1998 by
7166* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
7167*
7168* =====================================================================
7169*
7170* .. Parameters ..
7171 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
7172 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
7173 $ RSRC_
7174 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
7175 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
7176 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
7177 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
7178 REAL ZERO
7179 parameter( zero = 0.0e+0 )
7180* ..
7181* .. Local Scalars ..
7182 LOGICAL COLREP, GODOWN, GOLEFT, ROWREP
7183 INTEGER I, IACOL, IAROW, ICTXT, IIA, IJOFFA, ILOW,
7184 $ IMB1, IMBLOC, INB1, INBLOC, IOFFA, IOFFD, IUPP,
7185 $ JJA, JOFFA, JOFFD, LCMT, LCMT00, LDA, LDAP1,
7186 $ LMBLOC, LNBLOC, LOW, MB, MBLKD, MBLKS, MBLOC,
7187 $ MRCOL, MRROW, MYCOL, MYROW, NB, NBLKD, NBLKS,
7188 $ NBLOC, NP, NPCOL, NPROW, NQ, PMB, QNB, UPP
7189 REAL ALPHA, ATMP
7190* ..
7191* .. Local Arrays ..
7192 INTEGER DESCA2( DLEN_ )
7193* ..
7194* .. External Subroutines ..
7195 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
7196 $ pb_desctrans
7197* ..
7198* .. External Functions ..
7199 LOGICAL LSAME
7200 REAL PSLAMCH
7201 EXTERNAL lsame, pslamch
7202* ..
7203* .. Intrinsic Functions ..
7204 INTRINSIC cmplx, max, min, real
7205* ..
7206* .. Executable Statements ..
7207*
7208* Convert descriptor
7209*
7210 CALL pb_desctrans( desca, desca2 )
7211*
7212* Get grid parameters
7213*
7214 ictxt = desca2( ctxt_ )
7215 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
7216*
7217 IF( n.LE.0 )
7218 $ RETURN
7219*
7220 IF( lsame( toggle, 'Z' ) ) THEN
7221 alpha = zero
7222 ELSE IF( lsame( toggle, 'B' ) ) THEN
7223 alpha = pslamch( ictxt, 'Epsilon' )
7224 alpha = alpha / pslamch( ictxt, 'Safe minimum' )
7225 END IF
7226*
7227 CALL pb_ainfog2l( n, n, ia, ja, desca2, nprow, npcol, myrow,
7228 $ mycol, imb1, inb1, np, nq, iia, jja, iarow,
7229 $ iacol, mrrow, mrcol )
7230*
7231 IF( np.LE.0 .OR. nq.LE.0 )
7232 $ RETURN
7233*
7234* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC, LNBLOC,
7235* ILOW, LOW, IUPP, and UPP.
7236*
7237 mb = desca2( mb_ )
7238 nb = desca2( nb_ )
7239 CALL pb_binfo( 0, np, nq, imb1, inb1, mb, nb, mrrow, mrcol,
7240 $ lcmt00, mblks, nblks, imbloc, inbloc, lmbloc,
7241 $ lnbloc, ilow, low, iupp, upp )
7242*
7243 ioffa = iia - 1
7244 joffa = jja - 1
7245 rowrep = ( desca2( rsrc_ ).EQ.-1 )
7246 colrep = ( desca2( csrc_ ).EQ.-1 )
7247 lda = desca2( lld_ )
7248 ldap1 = lda + 1
7249*
7250 IF( rowrep ) THEN
7251 pmb = mb
7252 ELSE
7253 pmb = nprow * mb
7254 END IF
7255 IF( colrep ) THEN
7256 qnb = nb
7257 ELSE
7258 qnb = npcol * nb
7259 END IF
7260*
7261* Handle the first block of rows or columns separately, and update
7262* LCMT00, MBLKS and NBLKS.
7263*
7264 godown = ( lcmt00.GT.iupp )
7265 goleft = ( lcmt00.LT.ilow )
7266*
7267 IF( .NOT.godown .AND. .NOT.goleft ) THEN
7268*
7269* LCMT00 >= ILOW && LCMT00 <= IUPP
7270*
7271 IF( lcmt00.GE.0 ) THEN
7272 ijoffa = ioffa + lcmt00 + ( joffa - 1 ) * lda
7273 DO 10 i = 1, min( inbloc, max( 0, imbloc - lcmt00 ) )
7274 atmp = real( a( ijoffa + i*ldap1 ) )
7275 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7276 10 CONTINUE
7277 ELSE
7278 ijoffa = ioffa + ( joffa - lcmt00 - 1 ) * lda
7279 DO 20 i = 1, min( imbloc, max( 0, inbloc + lcmt00 ) )
7280 atmp = real( a( ijoffa + i*ldap1 ) )
7281 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7282 20 CONTINUE
7283 END IF
7284 goleft = ( ( lcmt00 - ( iupp - upp + pmb ) ).LT.ilow )
7285 godown = .NOT.goleft
7286*
7287 END IF
7288*
7289 IF( godown ) THEN
7290*
7291 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7292 mblks = mblks - 1
7293 ioffa = ioffa + imbloc
7294*
7295 30 CONTINUE
7296 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7297 lcmt00 = lcmt00 - pmb
7298 mblks = mblks - 1
7299 ioffa = ioffa + mb
7300 GO TO 30
7301 END IF
7302*
7303 IF( mblks.LE.0 )
7304 $ RETURN
7305*
7306 lcmt = lcmt00
7307 mblkd = mblks
7308 ioffd = ioffa
7309*
7310 mbloc = mb
7311 40 CONTINUE
7312 IF( mblkd.GT.0 .AND. lcmt.GE.ilow ) THEN
7313 IF( mblkd.EQ.1 )
7314 $ mbloc = lmbloc
7315 IF( lcmt.GE.0 ) THEN
7316 ijoffa = ioffd + lcmt + ( joffa - 1 ) * lda
7317 DO 50 i = 1, min( inbloc, max( 0, mbloc - lcmt ) )
7318 atmp = real( a( ijoffa + i*ldap1 ) )
7319 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7320 50 CONTINUE
7321 ELSE
7322 ijoffa = ioffd + ( joffa - lcmt - 1 ) * lda
7323 DO 60 i = 1, min( mbloc, max( 0, inbloc + lcmt ) )
7324 atmp = real( a( ijoffa + i*ldap1 ) )
7325 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7326 60 CONTINUE
7327 END IF
7328 lcmt00 = lcmt
7329 lcmt = lcmt - pmb
7330 mblks = mblkd
7331 mblkd = mblkd - 1
7332 ioffa = ioffd
7333 ioffd = ioffd + mbloc
7334 GO TO 40
7335 END IF
7336*
7337 lcmt00 = lcmt00 + low - ilow + qnb
7338 nblks = nblks - 1
7339 joffa = joffa + inbloc
7340*
7341 ELSE IF( goleft ) THEN
7342*
7343 lcmt00 = lcmt00 + low - ilow + qnb
7344 nblks = nblks - 1
7345 joffa = joffa + inbloc
7346*
7347 70 CONTINUE
7348 IF( nblks.GT.0 .AND. lcmt00.LT.low ) THEN
7349 lcmt00 = lcmt00 + qnb
7350 nblks = nblks - 1
7351 joffa = joffa + nb
7352 GO TO 70
7353 END IF
7354*
7355 IF( nblks.LE.0 )
7356 $ RETURN
7357*
7358 lcmt = lcmt00
7359 nblkd = nblks
7360 joffd = joffa
7361*
7362 nbloc = nb
7363 80 CONTINUE
7364 IF( nblkd.GT.0 .AND. lcmt.LE.iupp ) THEN
7365 IF( nblkd.EQ.1 )
7366 $ nbloc = lnbloc
7367 IF( lcmt.GE.0 ) THEN
7368 ijoffa = ioffa + lcmt + ( joffd - 1 ) * lda
7369 DO 90 i = 1, min( nbloc, max( 0, imbloc - lcmt ) )
7370 atmp = real( a( ijoffa + i*ldap1 ) )
7371 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7372 90 CONTINUE
7373 ELSE
7374 ijoffa = ioffa + ( joffd - lcmt - 1 ) * lda
7375 DO 100 i = 1, min( imbloc, max( 0, nbloc + lcmt ) )
7376 atmp = real( a( ijoffa + i*ldap1 ) )
7377 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7378 100 CONTINUE
7379 END IF
7380 lcmt00 = lcmt
7381 lcmt = lcmt + qnb
7382 nblks = nblkd
7383 nblkd = nblkd - 1
7384 joffa = joffd
7385 joffd = joffd + nbloc
7386 GO TO 80
7387 END IF
7388*
7389 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7390 mblks = mblks - 1
7391 ioffa = ioffa + imbloc
7392*
7393 END IF
7394*
7395 nbloc = nb
7396 110 CONTINUE
7397 IF( nblks.GT.0 ) THEN
7398 IF( nblks.EQ.1 )
7399 $ nbloc = lnbloc
7400 120 CONTINUE
7401 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7402 lcmt00 = lcmt00 - pmb
7403 mblks = mblks - 1
7404 ioffa = ioffa + mb
7405 GO TO 120
7406 END IF
7407*
7408 IF( mblks.LE.0 )
7409 $ RETURN
7410*
7411 lcmt = lcmt00
7412 mblkd = mblks
7413 ioffd = ioffa
7414*
7415 mbloc = mb
7416 130 CONTINUE
7417 IF( mblkd.GT.0 .AND. lcmt.GE.low ) THEN
7418 IF( mblkd.EQ.1 )
7419 $ mbloc = lmbloc
7420 IF( lcmt.GE.0 ) THEN
7421 ijoffa = ioffd + lcmt + ( joffa - 1 ) * lda
7422 DO 140 i = 1, min( nbloc, max( 0, mbloc - lcmt ) )
7423 atmp = real( a( ijoffa + i*ldap1 ) )
7424 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7425 140 CONTINUE
7426 ELSE
7427 ijoffa = ioffd + ( joffa - lcmt - 1 ) * lda
7428 DO 150 i = 1, min( mbloc, max( 0, nbloc + lcmt ) )
7429 atmp = real( a( ijoffa + i*ldap1 ) )
7430 a( ijoffa + i*ldap1 ) = cmplx( atmp, alpha )
7431 150 CONTINUE
7432 END IF
7433 lcmt00 = lcmt
7434 lcmt = lcmt - pmb
7435 mblks = mblkd
7436 mblkd = mblkd - 1
7437 ioffa = ioffd
7438 ioffd = ioffd + mbloc
7439 GO TO 130
7440 END IF
7441*
7442 lcmt00 = lcmt00 + qnb
7443 nblks = nblks - 1
7444 joffa = joffa + nbloc
7445 GO TO 110
7446*
7447 END IF
7448*
7449 RETURN
7450*
7451* End of PCIPSET
7452*
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
real function pslamch(ictxt, cmach)
Definition pcblastst.f:7455
#define max(A, B)
Definition pcgemr.c:180
#define min(A, B)
Definition pcgemr.c:181
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: