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

◆ pzlaset()

subroutine pzlaset ( character*1  uplo,
integer  m,
integer  n,
complex*16  alpha,
complex*16  beta,
complex*16, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 7508 of file pzblastst.f.

7509*
7510* -- PBLAS test routine (version 2.0) --
7511* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
7512* and University of California, Berkeley.
7513* April 1, 1998
7514*
7515* .. Scalar Arguments ..
7516 CHARACTER*1 UPLO
7517 INTEGER IA, JA, M, N
7518 COMPLEX*16 ALPHA, BETA
7519* ..
7520* .. Array Arguments ..
7521 INTEGER DESCA( * )
7522 COMPLEX*16 A( * )
7523* ..
7524*
7525* Purpose
7526* =======
7527*
7528* PZLASET initializes an m by n submatrix A(IA:IA+M-1,JA:JA+N-1) deno-
7529* ted by sub( A ) to beta on the diagonal and alpha on the offdiago-
7530* nals.
7531*
7532* Notes
7533* =====
7534*
7535* A description vector is associated with each 2D block-cyclicly dis-
7536* tributed matrix. This vector stores the information required to
7537* establish the mapping between a matrix entry and its corresponding
7538* process and memory location.
7539*
7540* In the following comments, the character _ should be read as
7541* "of the distributed matrix". Let A be a generic term for any 2D
7542* block cyclicly distributed matrix. Its description vector is DESCA:
7543*
7544* NOTATION STORED IN EXPLANATION
7545* ---------------- --------------- ------------------------------------
7546* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
7547* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
7548* the NPROW x NPCOL BLACS process grid
7549* A is distributed over. The context
7550* itself is global, but the handle
7551* (the integer value) may vary.
7552* M_A (global) DESCA( M_ ) The number of rows in the distribu-
7553* ted matrix A, M_A >= 0.
7554* N_A (global) DESCA( N_ ) The number of columns in the distri-
7555* buted matrix A, N_A >= 0.
7556* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
7557* block of the matrix A, IMB_A > 0.
7558* INB_A (global) DESCA( INB_ ) The number of columns of the upper
7559* left block of the matrix A,
7560* INB_A > 0.
7561* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
7562* bute the last M_A-IMB_A rows of A,
7563* MB_A > 0.
7564* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
7565* bute the last N_A-INB_A columns of
7566* A, NB_A > 0.
7567* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
7568* row of the matrix A is distributed,
7569* NPROW > RSRC_A >= 0.
7570* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
7571* first column of A is distributed.
7572* NPCOL > CSRC_A >= 0.
7573* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
7574* array storing the local blocks of
7575* the distributed matrix A,
7576* IF( Lc( 1, N_A ) > 0 )
7577* LLD_A >= MAX( 1, Lr( 1, M_A ) )
7578* ELSE
7579* LLD_A >= 1.
7580*
7581* Let K be the number of rows of a matrix A starting at the global in-
7582* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
7583* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
7584* receive if these K rows were distributed over NPROW processes. If K
7585* is the number of columns of a matrix A starting at the global index
7586* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
7587* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
7588* these K columns were distributed over NPCOL processes.
7589*
7590* The values of Lr() and Lc() may be determined via a call to the func-
7591* tion PB_NUMROC:
7592* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
7593* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
7594*
7595* Arguments
7596* =========
7597*
7598* UPLO (global input) CHARACTER*1
7599* On entry, UPLO specifies the part of the submatrix sub( A )
7600* to be set:
7601* = 'L' or 'l': Lower triangular part is set; the strictly
7602* upper triangular part of sub( A ) is not changed;
7603* = 'U' or 'u': Upper triangular part is set; the strictly
7604* lower triangular part of sub( A ) is not changed;
7605* Otherwise: All of the matrix sub( A ) is set.
7606*
7607* M (global input) INTEGER
7608* On entry, M specifies the number of rows of the submatrix
7609* sub( A ). M must be at least zero.
7610*
7611* N (global input) INTEGER
7612* On entry, N specifies the number of columns of the submatrix
7613* sub( A ). N must be at least zero.
7614*
7615* ALPHA (global input) COMPLEX*16
7616* On entry, ALPHA specifies the scalar alpha, i.e., the cons-
7617* tant to which the offdiagonal elements are to be set.
7618*
7619* BETA (global input) COMPLEX*16
7620* On entry, BETA specifies the scalar beta, i.e., the constant
7621* to which the diagonal elements are to be set.
7622*
7623* A (local input/local output) COMPLEX*16 array
7624* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
7625* at least Lc( 1, JA+N-1 ). Before entry, this array contains
7626* the local entries of the matrix A to be set. On exit, the
7627* leading m by n submatrix sub( A ) is set as follows:
7628*
7629* if UPLO = 'U', A(IA+i-1,JA+j-1) = ALPHA, 1<=i<=j-1, 1<=j<=N,
7630* if UPLO = 'L', A(IA+i-1,JA+j-1) = ALPHA, j+1<=i<=M, 1<=j<=N,
7631* otherwise, A(IA+i-1,JA+j-1) = ALPHA, 1<=i<=M, 1<=j<=N,
7632* and IA+i.NE.JA+j,
7633* and, for all UPLO, A(IA+i-1,JA+i-1) = BETA, 1<=i<=min(M,N).
7634*
7635* IA (global input) INTEGER
7636* On entry, IA specifies A's global row index, which points to
7637* the beginning of the submatrix sub( A ).
7638*
7639* JA (global input) INTEGER
7640* On entry, JA specifies A's global column index, which points
7641* to the beginning of the submatrix sub( A ).
7642*
7643* DESCA (global and local input) INTEGER array
7644* On entry, DESCA is an integer array of dimension DLEN_. This
7645* is the array descriptor for the matrix A.
7646*
7647* -- Written on April 1, 1998 by
7648* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
7649*
7650* =====================================================================
7651*
7652* .. Parameters ..
7653 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
7654 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
7655 $ RSRC_
7656 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
7657 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
7658 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
7659 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
7660* ..
7661* .. Local Scalars ..
7662 LOGICAL GODOWN, GOLEFT, ISCOLREP, ISROWREP, LOWER,
7663 $ UPPER
7664 INTEGER IACOL, IAROW, ICTXT, IIA, IIMAX, ILOW, IMB1,
7665 $ IMBLOC, INB1, INBLOC, IOFFA, IOFFD, IUPP, JJA,
7666 $ JJMAX, JOFFA, JOFFD, LCMT, LCMT00, LDA, LMBLOC,
7667 $ LNBLOC, LOW, M1, MB, MBLKD, MBLKS, MBLOC, MP,
7668 $ MRCOL, MRROW, MYCOL, MYROW, N1, NB, NBLKD,
7669 $ NBLKS, NBLOC, NPCOL, NPROW, NQ, PMB, QNB, TMP1,
7670 $ UPP
7671* ..
7672* .. Local Arrays ..
7673 INTEGER DESCA2( DLEN_ )
7674* ..
7675* .. External Subroutines ..
7676 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
7678* ..
7679* .. External Functions ..
7680 LOGICAL LSAME
7681 EXTERNAL lsame
7682* ..
7683* .. Intrinsic Functions ..
7684 INTRINSIC min
7685* ..
7686* .. Executable Statements ..
7687*
7688 IF( m.EQ.0 .OR. n.EQ.0 )
7689 $ RETURN
7690*
7691* Convert descriptor
7692*
7693 CALL pb_desctrans( desca, desca2 )
7694*
7695* Get grid parameters
7696*
7697 ictxt = desca2( ctxt_ )
7698 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
7699*
7700 CALL pb_ainfog2l( m, n, ia, ja, desca2, nprow, npcol, myrow,
7701 $ mycol, imb1, inb1, mp, nq, iia, jja, iarow,
7702 $ iacol, mrrow, mrcol )
7703*
7704 IF( mp.LE.0 .OR. nq.LE.0 )
7705 $ RETURN
7706*
7707 isrowrep = ( desca2( rsrc_ ).LT.0 )
7708 iscolrep = ( desca2( csrc_ ).LT.0 )
7709 lda = desca2( lld_ )
7710*
7711 upper = .NOT.( lsame( uplo, 'L' ) )
7712 lower = .NOT.( lsame( uplo, 'U' ) )
7713*
7714 IF( ( ( lower.AND.upper ).AND.( alpha.EQ.beta ) ).OR.
7715 $ ( isrowrep .AND. iscolrep ) ) THEN
7716 IF( ( mp.GT.0 ).AND.( nq.GT.0 ) )
7717 $ CALL pb_zlaset( uplo, mp, nq, 0, alpha, beta,
7718 $ a( iia + ( jja - 1 ) * lda ), lda )
7719 RETURN
7720 END IF
7721*
7722* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC, LNBLOC,
7723* ILOW, LOW, IUPP, and UPP.
7724*
7725 mb = desca2( mb_ )
7726 nb = desca2( nb_ )
7727 CALL pb_binfo( 0, mp, nq, imb1, inb1, mb, nb, mrrow, mrcol,
7728 $ lcmt00, mblks, nblks, imbloc, inbloc, lmbloc,
7729 $ lnbloc, ilow, low, iupp, upp )
7730*
7731 ioffa = iia - 1
7732 joffa = jja - 1
7733 iimax = ioffa + mp
7734 jjmax = joffa + nq
7735*
7736 IF( isrowrep ) THEN
7737 pmb = mb
7738 ELSE
7739 pmb = nprow * mb
7740 END IF
7741 IF( iscolrep ) THEN
7742 qnb = nb
7743 ELSE
7744 qnb = npcol * nb
7745 END IF
7746*
7747 m1 = mp
7748 n1 = nq
7749*
7750* Handle the first block of rows or columns separately, and update
7751* LCMT00, MBLKS and NBLKS.
7752*
7753 godown = ( lcmt00.GT.iupp )
7754 goleft = ( lcmt00.LT.ilow )
7755*
7756 IF( .NOT.godown .AND. .NOT.goleft ) THEN
7757*
7758* LCMT00 >= ILOW && LCMT00 <= IUPP
7759*
7760 goleft = ( ( lcmt00 - ( iupp - upp + pmb ) ).LT.ilow )
7761 godown = .NOT.goleft
7762*
7763 CALL pb_zlaset( uplo, imbloc, inbloc, lcmt00, alpha, beta,
7764 $ a( iia+joffa*lda ), lda )
7765 IF( godown ) THEN
7766 IF( upper .AND. nq.GT.inbloc )
7767 $ CALL pb_zlaset( 'All', imbloc, nq-inbloc, 0, alpha,
7768 $ alpha, a( iia+(joffa+inbloc)*lda ), lda )
7769 iia = iia + imbloc
7770 m1 = m1 - imbloc
7771 ELSE
7772 IF( lower .AND. mp.GT.imbloc )
7773 $ CALL pb_zlaset( 'All', mp-imbloc, inbloc, 0, alpha,
7774 $ alpha, a( iia+imbloc+joffa*lda ), lda )
7775 jja = jja + inbloc
7776 n1 = n1 - inbloc
7777 END IF
7778*
7779 END IF
7780*
7781 IF( godown ) THEN
7782*
7783 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7784 mblks = mblks - 1
7785 ioffa = ioffa + imbloc
7786*
7787 10 CONTINUE
7788 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7789 lcmt00 = lcmt00 - pmb
7790 mblks = mblks - 1
7791 ioffa = ioffa + mb
7792 GO TO 10
7793 END IF
7794*
7795 tmp1 = min( ioffa, iimax ) - iia + 1
7796 IF( upper .AND. tmp1.GT.0 ) THEN
7797 CALL pb_zlaset( 'All', tmp1, n1, 0, alpha, alpha,
7798 $ a( iia+joffa*lda ), lda )
7799 iia = iia + tmp1
7800 m1 = m1 - tmp1
7801 END IF
7802*
7803 IF( mblks.LE.0 )
7804 $ RETURN
7805*
7806 lcmt = lcmt00
7807 mblkd = mblks
7808 ioffd = ioffa
7809*
7810 mbloc = mb
7811 20 CONTINUE
7812 IF( mblkd.GT.0 .AND. lcmt.GE.ilow ) THEN
7813 IF( mblkd.EQ.1 )
7814 $ mbloc = lmbloc
7815 CALL pb_zlaset( uplo, mbloc, inbloc, lcmt, alpha, beta,
7816 $ a( ioffd+1+joffa*lda ), lda )
7817 lcmt00 = lcmt
7818 lcmt = lcmt - pmb
7819 mblks = mblkd
7820 mblkd = mblkd - 1
7821 ioffa = ioffd
7822 ioffd = ioffd + mbloc
7823 GO TO 20
7824 END IF
7825*
7826 tmp1 = m1 - ioffd + iia - 1
7827 IF( lower .AND. tmp1.GT.0 )
7828 $ CALL pb_zlaset( 'ALL', tmp1, inbloc, 0, alpha, alpha,
7829 $ a( ioffd+1+joffa*lda ), lda )
7830*
7831 tmp1 = ioffa - iia + 1
7832 m1 = m1 - tmp1
7833 n1 = n1 - inbloc
7834 lcmt00 = lcmt00 + low - ilow + qnb
7835 nblks = nblks - 1
7836 joffa = joffa + inbloc
7837*
7838 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
7839 $ CALL pb_zlaset( 'ALL', tmp1, n1, 0, alpha, alpha,
7840 $ a( iia+joffa*lda ), lda )
7841*
7842 iia = ioffa + 1
7843 jja = joffa + 1
7844*
7845 ELSE IF( goleft ) THEN
7846*
7847 lcmt00 = lcmt00 + low - ilow + qnb
7848 nblks = nblks - 1
7849 joffa = joffa + inbloc
7850*
7851 30 CONTINUE
7852 IF( nblks.GT.0 .AND. lcmt00.LT.low ) THEN
7853 lcmt00 = lcmt00 + qnb
7854 nblks = nblks - 1
7855 joffa = joffa + nb
7856 GO TO 30
7857 END IF
7858*
7859 tmp1 = min( joffa, jjmax ) - jja + 1
7860 IF( lower .AND. tmp1.GT.0 ) THEN
7861 CALL pb_zlaset( 'All', m1, tmp1, 0, alpha, alpha,
7862 $ a( iia+(jja-1)*lda ), lda )
7863 jja = jja + tmp1
7864 n1 = n1 - tmp1
7865 END IF
7866*
7867 IF( nblks.LE.0 )
7868 $ RETURN
7869*
7870 lcmt = lcmt00
7871 nblkd = nblks
7872 joffd = joffa
7873*
7874 nbloc = nb
7875 40 CONTINUE
7876 IF( nblkd.GT.0 .AND. lcmt.LE.iupp ) THEN
7877 IF( nblkd.EQ.1 )
7878 $ nbloc = lnbloc
7879 CALL pb_zlaset( uplo, imbloc, nbloc, lcmt, alpha, beta,
7880 $ a( iia+joffd*lda ), lda )
7881 lcmt00 = lcmt
7882 lcmt = lcmt + qnb
7883 nblks = nblkd
7884 nblkd = nblkd - 1
7885 joffa = joffd
7886 joffd = joffd + nbloc
7887 GO TO 40
7888 END IF
7889*
7890 tmp1 = n1 - joffd + jja - 1
7891 IF( upper .AND. tmp1.GT.0 )
7892 $ CALL pb_zlaset( 'All', imbloc, tmp1, 0, alpha, alpha,
7893 $ a( iia+joffd*lda ), lda )
7894*
7895 tmp1 = joffa - jja + 1
7896 m1 = m1 - imbloc
7897 n1 = n1 - tmp1
7898 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7899 mblks = mblks - 1
7900 ioffa = ioffa + imbloc
7901*
7902 IF( lower .AND. m1.GT.0 .AND. tmp1.GT.0 )
7903 $ CALL pb_zlaset( 'All', m1, tmp1, 0, alpha, alpha,
7904 $ a( ioffa+1+(jja-1)*lda ), lda )
7905*
7906 iia = ioffa + 1
7907 jja = joffa + 1
7908*
7909 END IF
7910*
7911 nbloc = nb
7912 50 CONTINUE
7913 IF( nblks.GT.0 ) THEN
7914 IF( nblks.EQ.1 )
7915 $ nbloc = lnbloc
7916 60 CONTINUE
7917 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7918 lcmt00 = lcmt00 - pmb
7919 mblks = mblks - 1
7920 ioffa = ioffa + mb
7921 GO TO 60
7922 END IF
7923*
7924 tmp1 = min( ioffa, iimax ) - iia + 1
7925 IF( upper .AND. tmp1.GT.0 ) THEN
7926 CALL pb_zlaset( 'All', tmp1, n1, 0, alpha, alpha,
7927 $ a( iia+joffa*lda ), lda )
7928 iia = iia + tmp1
7929 m1 = m1 - tmp1
7930 END IF
7931*
7932 IF( mblks.LE.0 )
7933 $ RETURN
7934*
7935 lcmt = lcmt00
7936 mblkd = mblks
7937 ioffd = ioffa
7938*
7939 mbloc = mb
7940 70 CONTINUE
7941 IF( mblkd.GT.0 .AND. lcmt.GE.low ) THEN
7942 IF( mblkd.EQ.1 )
7943 $ mbloc = lmbloc
7944 CALL pb_zlaset( uplo, mbloc, nbloc, lcmt, alpha, beta,
7945 $ a( ioffd+1+joffa*lda ), lda )
7946 lcmt00 = lcmt
7947 lcmt = lcmt - pmb
7948 mblks = mblkd
7949 mblkd = mblkd - 1
7950 ioffa = ioffd
7951 ioffd = ioffd + mbloc
7952 GO TO 70
7953 END IF
7954*
7955 tmp1 = m1 - ioffd + iia - 1
7956 IF( lower .AND. tmp1.GT.0 )
7957 $ CALL pb_zlaset( 'All', tmp1, nbloc, 0, alpha, alpha,
7958 $ a( ioffd+1+joffa*lda ), lda )
7959*
7960 tmp1 = min( ioffa, iimax ) - iia + 1
7961 m1 = m1 - tmp1
7962 n1 = n1 - nbloc
7963 lcmt00 = lcmt00 + qnb
7964 nblks = nblks - 1
7965 joffa = joffa + nbloc
7966*
7967 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
7968 $ CALL pb_zlaset( 'All', tmp1, n1, 0, alpha, alpha,
7969 $ a( iia+joffa*lda ), lda )
7970*
7971 iia = ioffa + 1
7972 jja = joffa + 1
7973*
7974 GO TO 50
7975*
7976 END IF
7977*
7978 RETURN
7979*
7980* End of PZLASET
7981*
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 min(A, B)
Definition pcgemr.c:181
subroutine pb_zlaset(uplo, m, n, ioffd, alpha, beta, a, lda)
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: