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

◆ psladom()

subroutine psladom ( logical  inplace,
integer  n,
real  alpha,
real, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 8243 of file psblastst.f.

8244*
8245* -- PBLAS test routine (version 2.0) --
8246* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
8247* and University of California, Berkeley.
8248* April 1, 1998
8249*
8250* .. Scalar Arguments ..
8251 LOGICAL INPLACE
8252 INTEGER IA, JA, N
8253 REAL ALPHA
8254* ..
8255* .. Array Arguments ..
8256 INTEGER DESCA( * )
8257 REAL A( * )
8258* ..
8259*
8260* Purpose
8261* =======
8262*
8263* PSLADOM adds alpha to the diagonal entries of an n by n submatrix
8264* sub( A ) denoting A( IA:IA+N-1, JA:JA+N-1 ).
8265*
8266* Notes
8267* =====
8268*
8269* A description vector is associated with each 2D block-cyclicly dis-
8270* tributed matrix. This vector stores the information required to
8271* establish the mapping between a matrix entry and its corresponding
8272* process and memory location.
8273*
8274* In the following comments, the character _ should be read as
8275* "of the distributed matrix". Let A be a generic term for any 2D
8276* block cyclicly distributed matrix. Its description vector is DESCA:
8277*
8278* NOTATION STORED IN EXPLANATION
8279* ---------------- --------------- ------------------------------------
8280* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
8281* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
8282* the NPROW x NPCOL BLACS process grid
8283* A is distributed over. The context
8284* itself is global, but the handle
8285* (the integer value) may vary.
8286* M_A (global) DESCA( M_ ) The number of rows in the distribu-
8287* ted matrix A, M_A >= 0.
8288* N_A (global) DESCA( N_ ) The number of columns in the distri-
8289* buted matrix A, N_A >= 0.
8290* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
8291* block of the matrix A, IMB_A > 0.
8292* INB_A (global) DESCA( INB_ ) The number of columns of the upper
8293* left block of the matrix A,
8294* INB_A > 0.
8295* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
8296* bute the last M_A-IMB_A rows of A,
8297* MB_A > 0.
8298* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
8299* bute the last N_A-INB_A columns of
8300* A, NB_A > 0.
8301* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
8302* row of the matrix A is distributed,
8303* NPROW > RSRC_A >= 0.
8304* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
8305* first column of A is distributed.
8306* NPCOL > CSRC_A >= 0.
8307* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
8308* array storing the local blocks of
8309* the distributed matrix A,
8310* IF( Lc( 1, N_A ) > 0 )
8311* LLD_A >= MAX( 1, Lr( 1, M_A ) )
8312* ELSE
8313* LLD_A >= 1.
8314*
8315* Let K be the number of rows of a matrix A starting at the global in-
8316* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
8317* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
8318* receive if these K rows were distributed over NPROW processes. If K
8319* is the number of columns of a matrix A starting at the global index
8320* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
8321* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
8322* these K columns were distributed over NPCOL processes.
8323*
8324* The values of Lr() and Lc() may be determined via a call to the func-
8325* tion PB_NUMROC:
8326* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
8327* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
8328*
8329* Arguments
8330* =========
8331*
8332* INPLACE (global input) LOGICAL
8333* On entry, INPLACE specifies if the matrix should be generated
8334* in place or not. If INPLACE is .TRUE., the local random array
8335* to be generated will start in memory at the local memory lo-
8336* cation A( 1, 1 ), otherwise it will start at the local posi-
8337* tion induced by IA and JA.
8338*
8339* N (global input) INTEGER
8340* On entry, N specifies the global order of the submatrix
8341* sub( A ) to be modified. N must be at least zero.
8342*
8343* ALPHA (global input) REAL
8344* On entry, ALPHA specifies the scalar alpha.
8345*
8346* A (local input/local output) REAL array
8347* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
8348* at least Lc( 1, JA+N-1 ). Before entry, this array contains
8349* the local entries of the matrix A. On exit, the local entries
8350* of this array corresponding to the main diagonal of sub( A )
8351* have been updated.
8352*
8353* IA (global input) INTEGER
8354* On entry, IA specifies A's global row index, which points to
8355* the beginning of the submatrix sub( A ).
8356*
8357* JA (global input) INTEGER
8358* On entry, JA specifies A's global column index, which points
8359* to the beginning of the submatrix sub( A ).
8360*
8361* DESCA (global and local input) INTEGER array
8362* On entry, DESCA is an integer array of dimension DLEN_. This
8363* is the array descriptor for the matrix A.
8364*
8365* -- Written on April 1, 1998 by
8366* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
8367*
8368* =====================================================================
8369*
8370* .. Parameters ..
8371 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
8372 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
8373 $ RSRC_
8374 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
8375 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
8376 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
8377 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
8378* ..
8379* .. Local Scalars ..
8380 LOGICAL GODOWN, GOLEFT
8381 INTEGER I, IACOL, IAROW, ICTXT, IIA, IJOFFA, ILOW,
8382 $ IMB1, IMBLOC, INB1, INBLOC, IOFFA, IOFFD, IUPP,
8383 $ JJA, JOFFA, JOFFD, LCMT, LCMT00, LDA, LDAP1,
8384 $ LMBLOC, LNBLOC, LOW, MB, MBLKD, MBLKS, MBLOC,
8385 $ MRCOL, MRROW, MYCOL, MYROW, NB, NBLKD, NBLKS,
8386 $ NBLOC, NP, NPCOL, NPROW, NQ, PMB, QNB, UPP
8387 REAL ATMP
8388* ..
8389* .. Local Scalars ..
8390 INTEGER DESCA2( DLEN_ )
8391* ..
8392* .. External Subroutines ..
8393 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
8394 $ pb_desctrans
8395* ..
8396* .. Intrinsic Functions ..
8397 INTRINSIC abs, max, min
8398* ..
8399* .. Executable Statements ..
8400*
8401* Convert descriptor
8402*
8403 CALL pb_desctrans( desca, desca2 )
8404*
8405* Get grid parameters
8406*
8407 ictxt = desca2( ctxt_ )
8408 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
8409*
8410 IF( n.EQ.0 )
8411 $ RETURN
8412*
8413 CALL pb_ainfog2l( n, n, ia, ja, desca2, nprow, npcol, myrow,
8414 $ mycol, imb1, inb1, np, nq, iia, jja, iarow,
8415 $ iacol, mrrow, mrcol )
8416*
8417* Decide where the entries shall be stored in memory
8418*
8419 IF( inplace ) THEN
8420 iia = 1
8421 jja = 1
8422 END IF
8423*
8424* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC, LNBLOC,
8425* ILOW, LOW, IUPP, and UPP.
8426*
8427 mb = desca2( mb_ )
8428 nb = desca2( nb_ )
8429*
8430 CALL pb_binfo( 0, np, nq, imb1, inb1, mb, nb, mrrow, mrcol,
8431 $ lcmt00, mblks, nblks, imbloc, inbloc, lmbloc,
8432 $ lnbloc, ilow, low, iupp, upp )
8433*
8434 ioffa = iia - 1
8435 joffa = jja - 1
8436 lda = desca2( lld_ )
8437 ldap1 = lda + 1
8438*
8439 IF( desca2( rsrc_ ).LT.0 ) THEN
8440 pmb = mb
8441 ELSE
8442 pmb = nprow * mb
8443 END IF
8444 IF( desca2( csrc_ ).LT.0 ) THEN
8445 qnb = nb
8446 ELSE
8447 qnb = npcol * nb
8448 END IF
8449*
8450* Handle the first block of rows or columns separately, and update
8451* LCMT00, MBLKS and NBLKS.
8452*
8453 godown = ( lcmt00.GT.iupp )
8454 goleft = ( lcmt00.LT.ilow )
8455*
8456 IF( .NOT.godown .AND. .NOT.goleft ) THEN
8457*
8458* LCMT00 >= ILOW && LCMT00 <= IUPP
8459*
8460 IF( lcmt00.GE.0 ) THEN
8461 ijoffa = ioffa+lcmt00 + ( joffa - 1 ) * lda
8462 DO 10 i = 1, min( inbloc, max( 0, imbloc - lcmt00 ) )
8463 atmp = a( ijoffa + i*ldap1 )
8464 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8465 10 CONTINUE
8466 ELSE
8467 ijoffa = ioffa + ( joffa - lcmt00 - 1 ) * lda
8468 DO 20 i = 1, min( imbloc, max( 0, inbloc + lcmt00 ) )
8469 atmp = a( ijoffa + i*ldap1 )
8470 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8471 20 CONTINUE
8472 END IF
8473 goleft = ( ( lcmt00 - ( iupp - upp + pmb ) ).LT.ilow )
8474 godown = .NOT.goleft
8475*
8476 END IF
8477*
8478 IF( godown ) THEN
8479*
8480 lcmt00 = lcmt00 - ( iupp - upp + pmb )
8481 mblks = mblks - 1
8482 ioffa = ioffa + imbloc
8483*
8484 30 CONTINUE
8485 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
8486 lcmt00 = lcmt00 - pmb
8487 mblks = mblks - 1
8488 ioffa = ioffa + mb
8489 GO TO 30
8490 END IF
8491*
8492 lcmt = lcmt00
8493 mblkd = mblks
8494 ioffd = ioffa
8495*
8496 mbloc = mb
8497 40 CONTINUE
8498 IF( mblkd.GT.0 .AND. lcmt.GE.ilow ) THEN
8499 IF( mblkd.EQ.1 )
8500 $ mbloc = lmbloc
8501 IF( lcmt.GE.0 ) THEN
8502 ijoffa = ioffd + lcmt + ( joffa - 1 ) * lda
8503 DO 50 i = 1, min( inbloc, max( 0, mbloc - lcmt ) )
8504 atmp = a( ijoffa + i*ldap1 )
8505 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8506 50 CONTINUE
8507 ELSE
8508 ijoffa = ioffd + ( joffa - lcmt - 1 ) * lda
8509 DO 60 i = 1, min( mbloc, max( 0, inbloc + lcmt ) )
8510 atmp = a( ijoffa + i*ldap1 )
8511 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8512 60 CONTINUE
8513 END IF
8514 lcmt00 = lcmt
8515 lcmt = lcmt - pmb
8516 mblks = mblkd
8517 mblkd = mblkd - 1
8518 ioffa = ioffd
8519 ioffd = ioffd + mbloc
8520 GO TO 40
8521 END IF
8522*
8523 lcmt00 = lcmt00 + low - ilow + qnb
8524 nblks = nblks - 1
8525 joffa = joffa + inbloc
8526*
8527 ELSE IF( goleft ) THEN
8528*
8529 lcmt00 = lcmt00 + low - ilow + qnb
8530 nblks = nblks - 1
8531 joffa = joffa + inbloc
8532*
8533 70 CONTINUE
8534 IF( nblks.GT.0 .AND. lcmt00.LT.low ) THEN
8535 lcmt00 = lcmt00 + qnb
8536 nblks = nblks - 1
8537 joffa = joffa + nb
8538 GO TO 70
8539 END IF
8540*
8541 lcmt = lcmt00
8542 nblkd = nblks
8543 joffd = joffa
8544*
8545 nbloc = nb
8546 80 CONTINUE
8547 IF( nblkd.GT.0 .AND. lcmt.LE.iupp ) THEN
8548 IF( nblkd.EQ.1 )
8549 $ nbloc = lnbloc
8550 IF( lcmt.GE.0 ) THEN
8551 ijoffa = ioffa + lcmt + ( joffd - 1 ) * lda
8552 DO 90 i = 1, min( nbloc, max( 0, imbloc - lcmt ) )
8553 atmp = a( ijoffa + i*ldap1 )
8554 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8555 90 CONTINUE
8556 ELSE
8557 ijoffa = ioffa + ( joffd - lcmt - 1 ) * lda
8558 DO 100 i = 1, min( imbloc, max( 0, nbloc + lcmt ) )
8559 atmp = a( ijoffa + i*ldap1 )
8560 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8561 100 CONTINUE
8562 END IF
8563 lcmt00 = lcmt
8564 lcmt = lcmt + qnb
8565 nblks = nblkd
8566 nblkd = nblkd - 1
8567 joffa = joffd
8568 joffd = joffd + nbloc
8569 GO TO 80
8570 END IF
8571*
8572 lcmt00 = lcmt00 - ( iupp - upp + pmb )
8573 mblks = mblks - 1
8574 ioffa = ioffa + imbloc
8575*
8576 END IF
8577*
8578 nbloc = nb
8579 110 CONTINUE
8580 IF( nblks.GT.0 ) THEN
8581 IF( nblks.EQ.1 )
8582 $ nbloc = lnbloc
8583 120 CONTINUE
8584 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
8585 lcmt00 = lcmt00 - pmb
8586 mblks = mblks - 1
8587 ioffa = ioffa + mb
8588 GO TO 120
8589 END IF
8590*
8591 lcmt = lcmt00
8592 mblkd = mblks
8593 ioffd = ioffa
8594*
8595 mbloc = mb
8596 130 CONTINUE
8597 IF( mblkd.GT.0 .AND. lcmt.GE.low ) THEN
8598 IF( mblkd.EQ.1 )
8599 $ mbloc = lmbloc
8600 IF( lcmt.GE.0 ) THEN
8601 ijoffa = ioffd + lcmt + ( joffa - 1 ) * lda
8602 DO 140 i = 1, min( nbloc, max( 0, mbloc - lcmt ) )
8603 atmp = a( ijoffa + i*ldap1 )
8604 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8605 140 CONTINUE
8606 ELSE
8607 ijoffa = ioffd + ( joffa - lcmt - 1 ) * lda
8608 DO 150 i = 1, min( mbloc, max( 0, nbloc + lcmt ) )
8609 atmp = a( ijoffa + i*ldap1 )
8610 a( ijoffa + i*ldap1 ) = abs( atmp ) + alpha
8611 150 CONTINUE
8612 END IF
8613 lcmt00 = lcmt
8614 lcmt = lcmt - pmb
8615 mblks = mblkd
8616 mblkd = mblkd - 1
8617 ioffa = ioffd
8618 ioffd = ioffd + mbloc
8619 GO TO 130
8620 END IF
8621*
8622 lcmt00 = lcmt00 + qnb
8623 nblks = nblks - 1
8624 joffa = joffa + nbloc
8625 GO TO 110
8626*
8627 END IF
8628*
8629 RETURN
8630*
8631* End of PSLADOM
8632*
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: