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

◆ pdladom()

subroutine pdladom ( logical  inplace,
integer  n,
double precision  alpha,
double precision, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 8241 of file pdblastst.f.

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