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

◆ pslascal()

subroutine pslascal ( character*1  type,
integer  m,
integer  n,
real  alpha,
real, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 7337 of file psblastst.f.

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