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

◆ pzipset()

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

Definition at line 7044 of file pzblastst.f.

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