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

◆ pdlascal()

subroutine pdlascal ( character*1  type,
integer  m,
integer  n,
double precision  alpha,
double precision, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 7336 of file pdblastst.f.

7337*
7338* -- PBLAS test routine (version 2.0) --
7339* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
7340* and University of California, Berkeley.
7341* April 1, 1998
7342*
7343* .. Scalar Arguments ..
7344 CHARACTER*1 TYPE
7345 INTEGER IA, JA, M, N
7346 DOUBLE PRECISION ALPHA
7347* ..
7348* .. Array Arguments ..
7349 INTEGER DESCA( * )
7350 DOUBLE PRECISION A( * )
7351* ..
7352*
7353* Purpose
7354* =======
7355*
7356* PDLASCAL scales the m by n submatrix A(IA:IA+M-1,JA:JA+N-1) denoted
7357* by sub( A ) by the scalar alpha. TYPE specifies if sub( A ) is full,
7358* upper triangular, lower triangular or upper Hessenberg.
7359*
7360* Notes
7361* =====
7362*
7363* A description vector is associated with each 2D block-cyclicly dis-
7364* tributed matrix. This vector stores the information required to
7365* establish the mapping between a matrix entry and its corresponding
7366* process and memory location.
7367*
7368* In the following comments, the character _ should be read as
7369* "of the distributed matrix". Let A be a generic term for any 2D
7370* block cyclicly distributed matrix. Its description vector is DESCA:
7371*
7372* NOTATION STORED IN EXPLANATION
7373* ---------------- --------------- ------------------------------------
7374* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
7375* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
7376* the NPROW x NPCOL BLACS process grid
7377* A is distributed over. The context
7378* itself is global, but the handle
7379* (the integer value) may vary.
7380* M_A (global) DESCA( M_ ) The number of rows in the distribu-
7381* ted matrix A, M_A >= 0.
7382* N_A (global) DESCA( N_ ) The number of columns in the distri-
7383* buted matrix A, N_A >= 0.
7384* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
7385* block of the matrix A, IMB_A > 0.
7386* INB_A (global) DESCA( INB_ ) The number of columns of the upper
7387* left block of the matrix A,
7388* INB_A > 0.
7389* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
7390* bute the last M_A-IMB_A rows of A,
7391* MB_A > 0.
7392* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
7393* bute the last N_A-INB_A columns of
7394* A, NB_A > 0.
7395* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
7396* row of the matrix A is distributed,
7397* NPROW > RSRC_A >= 0.
7398* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
7399* first column of A is distributed.
7400* NPCOL > CSRC_A >= 0.
7401* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
7402* array storing the local blocks of
7403* the distributed matrix A,
7404* IF( Lc( 1, N_A ) > 0 )
7405* LLD_A >= MAX( 1, Lr( 1, M_A ) )
7406* ELSE
7407* LLD_A >= 1.
7408*
7409* Let K be the number of rows of a matrix A starting at the global in-
7410* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
7411* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
7412* receive if these K rows were distributed over NPROW processes. If K
7413* is the number of columns of a matrix A starting at the global index
7414* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
7415* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
7416* these K columns were distributed over NPCOL processes.
7417*
7418* The values of Lr() and Lc() may be determined via a call to the func-
7419* tion PB_NUMROC:
7420* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
7421* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
7422*
7423* Arguments
7424* =========
7425*
7426* TYPE (global input) CHARACTER*1
7427* On entry, TYPE specifies the type of the input submatrix as
7428* follows:
7429* = 'L' or 'l': sub( A ) is a lower triangular matrix,
7430* = 'U' or 'u': sub( A ) is an upper triangular matrix,
7431* = 'H' or 'h': sub( A ) is an upper Hessenberg matrix,
7432* otherwise sub( A ) is a full matrix.
7433*
7434* M (global input) INTEGER
7435* On entry, M specifies the number of rows of the submatrix
7436* sub( A ). M must be at least zero.
7437*
7438* N (global input) INTEGER
7439* On entry, N specifies the number of columns of the submatrix
7440* sub( A ). N must be at least zero.
7441*
7442* ALPHA (global input) DOUBLE PRECISION
7443* On entry, ALPHA specifies the scalar alpha.
7444*
7445* A (local input/local output) DOUBLE PRECISION array
7446* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
7447* at least Lc( 1, JA+N-1 ). Before entry, this array contains
7448* the local entries of the matrix A.
7449* On exit, the local entries of this array corresponding to the
7450* to the entries of the submatrix sub( A ) are overwritten by
7451* the local entries of the m by n scaled submatrix.
7452*
7453* IA (global input) INTEGER
7454* On entry, IA specifies A's global row index, which points to
7455* the beginning of the submatrix sub( A ).
7456*
7457* JA (global input) INTEGER
7458* On entry, JA specifies A's global column index, which points
7459* to the beginning of the submatrix sub( A ).
7460*
7461* DESCA (global and local input) INTEGER array
7462* On entry, DESCA is an integer array of dimension DLEN_. This
7463* is the array descriptor for the matrix A.
7464*
7465* -- Written on April 1, 1998 by
7466* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
7467*
7468* =====================================================================
7469*
7470* .. Parameters ..
7471 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
7472 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
7473 $ RSRC_
7474 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
7475 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
7476 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
7477 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
7478* ..
7479* .. Local Scalars ..
7480 CHARACTER*1 UPLO
7481 LOGICAL GODOWN, GOLEFT, LOWER, UPPER
7482 INTEGER IACOL, IAROW, ICTXT, IIA, IIMAX, ILOW, IMB1,
7483 $ IMBLOC, INB1, INBLOC, IOFFA, IOFFD, ITYPE,
7484 $ IUPP, JJA, JJMAX, JOFFA, JOFFD, LCMT, LCMT00,
7485 $ LDA, LMBLOC, LNBLOC, LOW, M1, MB, MBLKD, MBLKS,
7486 $ MBLOC, MP, MRCOL, MRROW, MYCOL, MYROW, N1, NB,
7487 $ NBLKD, NBLKS, NBLOC, NPCOL, NPROW, NQ, PMB,
7488 $ QNB, TMP1, UPP
7489* ..
7490* .. Local Arrays ..
7491 INTEGER DESCA2( DLEN_ )
7492* ..
7493* .. External Subroutines ..
7494 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
7496* ..
7497* .. External Functions ..
7498 LOGICAL LSAME
7499 INTEGER PB_NUMROC
7500 EXTERNAL lsame, pb_numroc
7501* ..
7502* .. Intrinsic Functions ..
7503 INTRINSIC min
7504* ..
7505* .. Executable Statements ..
7506*
7507* Convert descriptor
7508*
7509 CALL pb_desctrans( desca, desca2 )
7510*
7511* Get grid parameters
7512*
7513 ictxt = desca2( ctxt_ )
7514 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
7515*
7516* Quick return if possible
7517*
7518 IF( m.EQ.0 .OR. n.EQ.0 )
7519 $ RETURN
7520*
7521 IF( lsame( TYPE, 'L' ) ) THEN
7522 itype = 1
7523 uplo = TYPE
7524 upper = .false.
7525 lower = .true.
7526 ioffd = 0
7527 ELSE IF( lsame( TYPE, 'U' ) ) THEN
7528 itype = 2
7529 uplo = TYPE
7530 upper = .true.
7531 lower = .false.
7532 ioffd = 0
7533 ELSE IF( lsame( TYPE, 'H' ) ) THEN
7534 itype = 3
7535 uplo = 'U'
7536 upper = .true.
7537 lower = .false.
7538 ioffd = 1
7539 ELSE
7540 itype = 0
7541 uplo = 'A'
7542 upper = .true.
7543 lower = .true.
7544 ioffd = 0
7545 END IF
7546*
7547* Compute local indexes
7548*
7549 IF( itype.EQ.0 ) THEN
7550*
7551* Full matrix
7552*
7553 CALL pb_infog2l( ia, ja, desca2, nprow, npcol, myrow, mycol,
7554 $ iia, jja, iarow, iacol )
7555 mp = pb_numroc( m, ia, desca2( imb_ ), desca2( mb_ ), myrow,
7556 $ desca2( rsrc_ ), nprow )
7557 nq = pb_numroc( n, ja, desca2( inb_ ), desca2( nb_ ), mycol,
7558 $ desca2( csrc_ ), npcol )
7559*
7560 IF( mp.LE.0 .OR. nq.LE.0 )
7561 $ RETURN
7562*
7563 lda = desca2( lld_ )
7564 ioffa = iia + ( jja - 1 ) * lda
7565*
7566 CALL pb_dlascal( 'All', mp, nq, 0, alpha, a( ioffa ), lda )
7567*
7568 ELSE
7569*
7570* Trapezoidal matrix
7571*
7572 CALL pb_ainfog2l( m, n, ia, ja, desca2, nprow, npcol, myrow,
7573 $ mycol, imb1, inb1, mp, nq, iia, jja, iarow,
7574 $ iacol, mrrow, mrcol )
7575*
7576 IF( mp.LE.0 .OR. nq.LE.0 )
7577 $ RETURN
7578*
7579* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC,
7580* LNBLOC, ILOW, LOW, IUPP, and UPP.
7581*
7582 mb = desca2( mb_ )
7583 nb = desca2( nb_ )
7584 lda = desca2( lld_ )
7585*
7586 CALL pb_binfo( ioffd, mp, nq, imb1, inb1, mb, nb, mrrow,
7587 $ mrcol, lcmt00, mblks, nblks, imbloc, inbloc,
7588 $ lmbloc, lnbloc, ilow, low, iupp, upp )
7589*
7590 m1 = mp
7591 n1 = nq
7592 ioffa = iia - 1
7593 joffa = jja - 1
7594 iimax = ioffa + mp
7595 jjmax = joffa + nq
7596*
7597 IF( desca2( rsrc_ ).LT.0 ) THEN
7598 pmb = mb
7599 ELSE
7600 pmb = nprow * mb
7601 END IF
7602 IF( desca2( csrc_ ).LT.0 ) THEN
7603 qnb = nb
7604 ELSE
7605 qnb = npcol * nb
7606 END IF
7607*
7608* Handle the first block of rows or columns separately, and
7609* update LCMT00, MBLKS and NBLKS.
7610*
7611 godown = ( lcmt00.GT.iupp )
7612 goleft = ( lcmt00.LT.ilow )
7613*
7614 IF( .NOT.godown .AND. .NOT.goleft ) THEN
7615*
7616* LCMT00 >= ILOW && LCMT00 <= IUPP
7617*
7618 goleft = ( ( lcmt00 - ( iupp - upp + pmb ) ).LT.ilow )
7619 godown = .NOT.goleft
7620*
7621 CALL pb_dlascal( uplo, imbloc, inbloc, lcmt00, alpha,
7622 $ a( iia+joffa*lda ), lda )
7623 IF( godown ) THEN
7624 IF( upper .AND. nq.GT.inbloc )
7625 $ CALL pb_dlascal( 'All', imbloc, nq-inbloc, 0, alpha,
7626 $ a( iia+(joffa+inbloc)*lda ), lda )
7627 iia = iia + imbloc
7628 m1 = m1 - imbloc
7629 ELSE
7630 IF( lower .AND. mp.GT.imbloc )
7631 $ CALL pb_dlascal( 'All', mp-imbloc, inbloc, 0, alpha,
7632 $ a( iia+imbloc+joffa*lda ), lda )
7633 jja = jja + inbloc
7634 n1 = n1 - inbloc
7635 END IF
7636*
7637 END IF
7638*
7639 IF( godown ) THEN
7640*
7641 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7642 mblks = mblks - 1
7643 ioffa = ioffa + imbloc
7644*
7645 10 CONTINUE
7646 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7647 lcmt00 = lcmt00 - pmb
7648 mblks = mblks - 1
7649 ioffa = ioffa + mb
7650 GO TO 10
7651 END IF
7652*
7653 tmp1 = min( ioffa, iimax ) - iia + 1
7654 IF( upper .AND. tmp1.GT.0 ) THEN
7655 CALL pb_dlascal( 'All', tmp1, n1, 0, alpha,
7656 $ a( iia+joffa*lda ), lda )
7657 iia = iia + tmp1
7658 m1 = m1 - tmp1
7659 END IF
7660*
7661 IF( mblks.LE.0 )
7662 $ RETURN
7663*
7664 lcmt = lcmt00
7665 mblkd = mblks
7666 ioffd = ioffa
7667*
7668 mbloc = mb
7669 20 CONTINUE
7670 IF( mblkd.GT.0 .AND. lcmt.GE.ilow ) THEN
7671 IF( mblkd.EQ.1 )
7672 $ mbloc = lmbloc
7673 CALL pb_dlascal( uplo, mbloc, inbloc, lcmt, alpha,
7674 $ a( ioffd+1+joffa*lda ), lda )
7675 lcmt00 = lcmt
7676 lcmt = lcmt - pmb
7677 mblks = mblkd
7678 mblkd = mblkd - 1
7679 ioffa = ioffd
7680 ioffd = ioffd + mbloc
7681 GO TO 20
7682 END IF
7683*
7684 tmp1 = m1 - ioffd + iia - 1
7685 IF( lower .AND. tmp1.GT.0 )
7686 $ CALL pb_dlascal( 'All', tmp1, inbloc, 0, alpha,
7687 $ a( ioffd+1+joffa*lda ), lda )
7688*
7689 tmp1 = ioffa - iia + 1
7690 m1 = m1 - tmp1
7691 n1 = n1 - inbloc
7692 lcmt00 = lcmt00 + low - ilow + qnb
7693 nblks = nblks - 1
7694 joffa = joffa + inbloc
7695*
7696 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
7697 $ CALL pb_dlascal( 'All', tmp1, n1, 0, alpha,
7698 $ a( iia+joffa*lda ), lda )
7699*
7700 iia = ioffa + 1
7701 jja = joffa + 1
7702*
7703 ELSE IF( goleft ) THEN
7704*
7705 lcmt00 = lcmt00 + low - ilow + qnb
7706 nblks = nblks - 1
7707 joffa = joffa + inbloc
7708*
7709 30 CONTINUE
7710 IF( nblks.GT.0 .AND. lcmt00.LT.low ) THEN
7711 lcmt00 = lcmt00 + qnb
7712 nblks = nblks - 1
7713 joffa = joffa + nb
7714 GO TO 30
7715 END IF
7716*
7717 tmp1 = min( joffa, jjmax ) - jja + 1
7718 IF( lower .AND. tmp1.GT.0 ) THEN
7719 CALL pb_dlascal( 'All', m1, tmp1, 0, alpha,
7720 $ a( iia+(jja-1)*lda ), lda )
7721 jja = jja + tmp1
7722 n1 = n1 - tmp1
7723 END IF
7724*
7725 IF( nblks.LE.0 )
7726 $ RETURN
7727*
7728 lcmt = lcmt00
7729 nblkd = nblks
7730 joffd = joffa
7731*
7732 nbloc = nb
7733 40 CONTINUE
7734 IF( nblkd.GT.0 .AND. lcmt.LE.iupp ) THEN
7735 IF( nblkd.EQ.1 )
7736 $ nbloc = lnbloc
7737 CALL pb_dlascal( uplo, imbloc, nbloc, lcmt, alpha,
7738 $ a( iia+joffd*lda ), lda )
7739 lcmt00 = lcmt
7740 lcmt = lcmt + qnb
7741 nblks = nblkd
7742 nblkd = nblkd - 1
7743 joffa = joffd
7744 joffd = joffd + nbloc
7745 GO TO 40
7746 END IF
7747*
7748 tmp1 = n1 - joffd + jja - 1
7749 IF( upper .AND. tmp1.GT.0 )
7750 $ CALL pb_dlascal( 'All', imbloc, tmp1, 0, alpha,
7751 $ a( iia+joffd*lda ), lda )
7752*
7753 tmp1 = joffa - jja + 1
7754 m1 = m1 - imbloc
7755 n1 = n1 - tmp1
7756 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7757 mblks = mblks - 1
7758 ioffa = ioffa + imbloc
7759*
7760 IF( lower .AND. m1.GT.0 .AND. tmp1.GT.0 )
7761 $ CALL pb_dlascal( 'All', m1, tmp1, 0, alpha,
7762 $ a( ioffa+1+(jja-1)*lda ), lda )
7763*
7764 iia = ioffa + 1
7765 jja = joffa + 1
7766*
7767 END IF
7768*
7769 nbloc = nb
7770 50 CONTINUE
7771 IF( nblks.GT.0 ) THEN
7772 IF( nblks.EQ.1 )
7773 $ nbloc = lnbloc
7774 60 CONTINUE
7775 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7776 lcmt00 = lcmt00 - pmb
7777 mblks = mblks - 1
7778 ioffa = ioffa + mb
7779 GO TO 60
7780 END IF
7781*
7782 tmp1 = min( ioffa, iimax ) - iia + 1
7783 IF( upper .AND. tmp1.GT.0 ) THEN
7784 CALL pb_dlascal( 'All', tmp1, n1, 0, alpha,
7785 $ a( iia+joffa*lda ), lda )
7786 iia = iia + tmp1
7787 m1 = m1 - tmp1
7788 END IF
7789*
7790 IF( mblks.LE.0 )
7791 $ RETURN
7792*
7793 lcmt = lcmt00
7794 mblkd = mblks
7795 ioffd = ioffa
7796*
7797 mbloc = mb
7798 70 CONTINUE
7799 IF( mblkd.GT.0 .AND. lcmt.GE.low ) THEN
7800 IF( mblkd.EQ.1 )
7801 $ mbloc = lmbloc
7802 CALL pb_dlascal( uplo, mbloc, nbloc, lcmt, alpha,
7803 $ a( ioffd+1+joffa*lda ), lda )
7804 lcmt00 = lcmt
7805 lcmt = lcmt - pmb
7806 mblks = mblkd
7807 mblkd = mblkd - 1
7808 ioffa = ioffd
7809 ioffd = ioffd + mbloc
7810 GO TO 70
7811 END IF
7812*
7813 tmp1 = m1 - ioffd + iia - 1
7814 IF( lower .AND. tmp1.GT.0 )
7815 $ CALL pb_dlascal( 'All', tmp1, nbloc, 0, alpha,
7816 $ a( ioffd+1+joffa*lda ), lda )
7817*
7818 tmp1 = min( ioffa, iimax ) - iia + 1
7819 m1 = m1 - tmp1
7820 n1 = n1 - nbloc
7821 lcmt00 = lcmt00 + qnb
7822 nblks = nblks - 1
7823 joffa = joffa + nbloc
7824*
7825 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
7826 $ CALL pb_dlascal( 'All', tmp1, n1, 0, alpha,
7827 $ a( iia+joffa*lda ), lda )
7828*
7829 iia = ioffa + 1
7830 jja = joffa + 1
7831*
7832 GO TO 50
7833*
7834 END IF
7835*
7836 END IF
7837*
7838 RETURN
7839*
7840* End of PDLASCAL
7841*
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_infog2l(i, j, desc, nprow, npcol, myrow, mycol, ii, jj, prow, pcol)
Definition pblastst.f:1673
subroutine pb_desctrans(descin, descout)
Definition pblastst.f:2964
integer function pb_numroc(n, i, inb, nb, proc, srcproc, nprocs)
Definition pblastst.f:2548
#define min(A, B)
Definition pcgemr.c:181
subroutine pb_dlascal(uplo, m, n, ioffd, alpha, a, lda)
Definition pdblastst.f:9556
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: