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

◆ pslaset()

subroutine pslaset ( character*1  uplo,
integer  m,
integer  n,
real  alpha,
real  beta,
real, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 6862 of file psblastst.f.

6863*
6864* -- PBLAS test routine (version 2.0) --
6865* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
6866* and University of California, Berkeley.
6867* April 1, 1998
6868*
6869* .. Scalar Arguments ..
6870 CHARACTER*1 UPLO
6871 INTEGER IA, JA, M, N
6872 REAL ALPHA, BETA
6873* ..
6874* .. Array Arguments ..
6875 INTEGER DESCA( * )
6876 REAL A( * )
6877* ..
6878*
6879* Purpose
6880* =======
6881*
6882* PSLASET initializes an m by n submatrix A(IA:IA+M-1,JA:JA+N-1) deno-
6883* ted by sub( A ) to beta on the diagonal and alpha on the offdiago-
6884* nals.
6885*
6886* Notes
6887* =====
6888*
6889* A description vector is associated with each 2D block-cyclicly dis-
6890* tributed matrix. This vector stores the information required to
6891* establish the mapping between a matrix entry and its corresponding
6892* process and memory location.
6893*
6894* In the following comments, the character _ should be read as
6895* "of the distributed matrix". Let A be a generic term for any 2D
6896* block cyclicly distributed matrix. Its description vector is DESCA:
6897*
6898* NOTATION STORED IN EXPLANATION
6899* ---------------- --------------- ------------------------------------
6900* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
6901* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
6902* the NPROW x NPCOL BLACS process grid
6903* A is distributed over. The context
6904* itself is global, but the handle
6905* (the integer value) may vary.
6906* M_A (global) DESCA( M_ ) The number of rows in the distribu-
6907* ted matrix A, M_A >= 0.
6908* N_A (global) DESCA( N_ ) The number of columns in the distri-
6909* buted matrix A, N_A >= 0.
6910* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
6911* block of the matrix A, IMB_A > 0.
6912* INB_A (global) DESCA( INB_ ) The number of columns of the upper
6913* left block of the matrix A,
6914* INB_A > 0.
6915* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
6916* bute the last M_A-IMB_A rows of A,
6917* MB_A > 0.
6918* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
6919* bute the last N_A-INB_A columns of
6920* A, NB_A > 0.
6921* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
6922* row of the matrix A is distributed,
6923* NPROW > RSRC_A >= 0.
6924* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
6925* first column of A is distributed.
6926* NPCOL > CSRC_A >= 0.
6927* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
6928* array storing the local blocks of
6929* the distributed matrix A,
6930* IF( Lc( 1, N_A ) > 0 )
6931* LLD_A >= MAX( 1, Lr( 1, M_A ) )
6932* ELSE
6933* LLD_A >= 1.
6934*
6935* Let K be the number of rows of a matrix A starting at the global in-
6936* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
6937* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
6938* receive if these K rows were distributed over NPROW processes. If K
6939* is the number of columns of a matrix A starting at the global index
6940* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
6941* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
6942* these K columns were distributed over NPCOL processes.
6943*
6944* The values of Lr() and Lc() may be determined via a call to the func-
6945* tion PB_NUMROC:
6946* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
6947* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
6948*
6949* Arguments
6950* =========
6951*
6952* UPLO (global input) CHARACTER*1
6953* On entry, UPLO specifies the part of the submatrix sub( A )
6954* to be set:
6955* = 'L' or 'l': Lower triangular part is set; the strictly
6956* upper triangular part of sub( A ) is not changed;
6957* = 'U' or 'u': Upper triangular part is set; the strictly
6958* lower triangular part of sub( A ) is not changed;
6959* Otherwise: All of the matrix sub( A ) is set.
6960*
6961* M (global input) INTEGER
6962* On entry, M specifies the number of rows of the submatrix
6963* sub( A ). M must be at least zero.
6964*
6965* N (global input) INTEGER
6966* On entry, N specifies the number of columns of the submatrix
6967* sub( A ). N must be at least zero.
6968*
6969* ALPHA (global input) REAL
6970* On entry, ALPHA specifies the scalar alpha, i.e., the cons-
6971* tant to which the offdiagonal elements are to be set.
6972*
6973* BETA (global input) REAL
6974* On entry, BETA specifies the scalar beta, i.e., the constant
6975* to which the diagonal elements are to be set.
6976*
6977* A (local input/local output) REAL array
6978* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
6979* at least Lc( 1, JA+N-1 ). Before entry, this array contains
6980* the local entries of the matrix A to be set. On exit, the
6981* leading m by n submatrix sub( A ) is set as follows:
6982*
6983* if UPLO = 'U', A(IA+i-1,JA+j-1) = ALPHA, 1<=i<=j-1, 1<=j<=N,
6984* if UPLO = 'L', A(IA+i-1,JA+j-1) = ALPHA, j+1<=i<=M, 1<=j<=N,
6985* otherwise, A(IA+i-1,JA+j-1) = ALPHA, 1<=i<=M, 1<=j<=N,
6986* and IA+i.NE.JA+j,
6987* and, for all UPLO, A(IA+i-1,JA+i-1) = BETA, 1<=i<=min(M,N).
6988*
6989* IA (global input) INTEGER
6990* On entry, IA specifies A's global row index, which points to
6991* the beginning of the submatrix sub( A ).
6992*
6993* JA (global input) INTEGER
6994* On entry, JA specifies A's global column index, which points
6995* to the beginning of the submatrix sub( A ).
6996*
6997* DESCA (global and local input) INTEGER array
6998* On entry, DESCA is an integer array of dimension DLEN_. This
6999* is the array descriptor for the matrix A.
7000*
7001* -- Written on April 1, 1998 by
7002* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
7003*
7004* =====================================================================
7005*
7006* .. Parameters ..
7007 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
7008 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
7009 $ RSRC_
7010 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
7011 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
7012 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
7013 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
7014* ..
7015* .. Local Scalars ..
7016 LOGICAL GODOWN, GOLEFT, ISCOLREP, ISROWREP, LOWER,
7017 $ UPPER
7018 INTEGER IACOL, IAROW, ICTXT, IIA, IIMAX, ILOW, IMB1,
7019 $ IMBLOC, INB1, INBLOC, IOFFA, IOFFD, IUPP, JJA,
7020 $ JJMAX, JOFFA, JOFFD, LCMT, LCMT00, LDA, LMBLOC,
7021 $ LNBLOC, LOW, M1, MB, MBLKD, MBLKS, MBLOC, MP,
7022 $ MRCOL, MRROW, MYCOL, MYROW, N1, NB, NBLKD,
7023 $ NBLKS, NBLOC, NPCOL, NPROW, NQ, PMB, QNB, TMP1,
7024 $ UPP
7025* ..
7026* .. Local Arrays ..
7027 INTEGER DESCA2( DLEN_ )
7028* ..
7029* .. External Subroutines ..
7030 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
7032* ..
7033* .. External Functions ..
7034 LOGICAL LSAME
7035 EXTERNAL lsame
7036* ..
7037* .. Intrinsic Functions ..
7038 INTRINSIC min
7039* ..
7040* .. Executable Statements ..
7041*
7042 IF( m.EQ.0 .OR. n.EQ.0 )
7043 $ RETURN
7044*
7045* Convert descriptor
7046*
7047 CALL pb_desctrans( desca, desca2 )
7048*
7049* Get grid parameters
7050*
7051 ictxt = desca2( ctxt_ )
7052 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
7053*
7054 CALL pb_ainfog2l( m, n, ia, ja, desca2, nprow, npcol, myrow,
7055 $ mycol, imb1, inb1, mp, nq, iia, jja, iarow,
7056 $ iacol, mrrow, mrcol )
7057*
7058 IF( mp.LE.0 .OR. nq.LE.0 )
7059 $ RETURN
7060*
7061 isrowrep = ( desca2( rsrc_ ).LT.0 )
7062 iscolrep = ( desca2( csrc_ ).LT.0 )
7063 lda = desca2( lld_ )
7064*
7065 upper = .NOT.( lsame( uplo, 'L' ) )
7066 lower = .NOT.( lsame( uplo, 'U' ) )
7067*
7068 IF( ( ( lower.AND.upper ).AND.( alpha.EQ.beta ) ).OR.
7069 $ ( isrowrep .AND. iscolrep ) ) THEN
7070 IF( ( mp.GT.0 ).AND.( nq.GT.0 ) )
7071 $ CALL pb_slaset( uplo, mp, nq, 0, alpha, beta,
7072 $ a( iia + ( jja - 1 ) * lda ), lda )
7073 RETURN
7074 END IF
7075*
7076* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC, LNBLOC,
7077* ILOW, LOW, IUPP, and UPP.
7078*
7079 mb = desca2( mb_ )
7080 nb = desca2( nb_ )
7081 CALL pb_binfo( 0, mp, nq, imb1, inb1, mb, nb, mrrow, mrcol,
7082 $ lcmt00, mblks, nblks, imbloc, inbloc, lmbloc,
7083 $ lnbloc, ilow, low, iupp, upp )
7084*
7085 ioffa = iia - 1
7086 joffa = jja - 1
7087 iimax = ioffa + mp
7088 jjmax = joffa + nq
7089*
7090 IF( isrowrep ) THEN
7091 pmb = mb
7092 ELSE
7093 pmb = nprow * mb
7094 END IF
7095 IF( iscolrep ) THEN
7096 qnb = nb
7097 ELSE
7098 qnb = npcol * nb
7099 END IF
7100*
7101 m1 = mp
7102 n1 = nq
7103*
7104* Handle the first block of rows or columns separately, and update
7105* LCMT00, MBLKS and NBLKS.
7106*
7107 godown = ( lcmt00.GT.iupp )
7108 goleft = ( lcmt00.LT.ilow )
7109*
7110 IF( .NOT.godown .AND. .NOT.goleft ) THEN
7111*
7112* LCMT00 >= ILOW && LCMT00 <= IUPP
7113*
7114 goleft = ( ( lcmt00 - ( iupp - upp + pmb ) ).LT.ilow )
7115 godown = .NOT.goleft
7116*
7117 CALL pb_slaset( uplo, imbloc, inbloc, lcmt00, alpha, beta,
7118 $ a( iia+joffa*lda ), lda )
7119 IF( godown ) THEN
7120 IF( upper .AND. nq.GT.inbloc )
7121 $ CALL pb_slaset( 'All', imbloc, nq-inbloc, 0, alpha,
7122 $ alpha, a( iia+(joffa+inbloc)*lda ), lda )
7123 iia = iia + imbloc
7124 m1 = m1 - imbloc
7125 ELSE
7126 IF( lower .AND. mp.GT.imbloc )
7127 $ CALL pb_slaset( 'All', mp-imbloc, inbloc, 0, alpha,
7128 $ alpha, a( iia+imbloc+joffa*lda ), lda )
7129 jja = jja + inbloc
7130 n1 = n1 - inbloc
7131 END IF
7132*
7133 END IF
7134*
7135 IF( godown ) THEN
7136*
7137 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7138 mblks = mblks - 1
7139 ioffa = ioffa + imbloc
7140*
7141 10 CONTINUE
7142 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7143 lcmt00 = lcmt00 - pmb
7144 mblks = mblks - 1
7145 ioffa = ioffa + mb
7146 GO TO 10
7147 END IF
7148*
7149 tmp1 = min( ioffa, iimax ) - iia + 1
7150 IF( upper .AND. tmp1.GT.0 ) THEN
7151 CALL pb_slaset( 'All', tmp1, n1, 0, alpha, alpha,
7152 $ a( iia+joffa*lda ), lda )
7153 iia = iia + tmp1
7154 m1 = m1 - tmp1
7155 END IF
7156*
7157 IF( mblks.LE.0 )
7158 $ RETURN
7159*
7160 lcmt = lcmt00
7161 mblkd = mblks
7162 ioffd = ioffa
7163*
7164 mbloc = mb
7165 20 CONTINUE
7166 IF( mblkd.GT.0 .AND. lcmt.GE.ilow ) THEN
7167 IF( mblkd.EQ.1 )
7168 $ mbloc = lmbloc
7169 CALL pb_slaset( uplo, mbloc, inbloc, lcmt, alpha, beta,
7170 $ a( ioffd+1+joffa*lda ), lda )
7171 lcmt00 = lcmt
7172 lcmt = lcmt - pmb
7173 mblks = mblkd
7174 mblkd = mblkd - 1
7175 ioffa = ioffd
7176 ioffd = ioffd + mbloc
7177 GO TO 20
7178 END IF
7179*
7180 tmp1 = m1 - ioffd + iia - 1
7181 IF( lower .AND. tmp1.GT.0 )
7182 $ CALL pb_slaset( 'ALL', tmp1, inbloc, 0, alpha, alpha,
7183 $ a( ioffd+1+joffa*lda ), lda )
7184*
7185 tmp1 = ioffa - iia + 1
7186 m1 = m1 - tmp1
7187 n1 = n1 - inbloc
7188 lcmt00 = lcmt00 + low - ilow + qnb
7189 nblks = nblks - 1
7190 joffa = joffa + inbloc
7191*
7192 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
7193 $ CALL pb_slaset( 'ALL', tmp1, n1, 0, alpha, alpha,
7194 $ a( iia+joffa*lda ), lda )
7195*
7196 iia = ioffa + 1
7197 jja = joffa + 1
7198*
7199 ELSE IF( goleft ) THEN
7200*
7201 lcmt00 = lcmt00 + low - ilow + qnb
7202 nblks = nblks - 1
7203 joffa = joffa + inbloc
7204*
7205 30 CONTINUE
7206 IF( nblks.GT.0 .AND. lcmt00.LT.low ) THEN
7207 lcmt00 = lcmt00 + qnb
7208 nblks = nblks - 1
7209 joffa = joffa + nb
7210 GO TO 30
7211 END IF
7212*
7213 tmp1 = min( joffa, jjmax ) - jja + 1
7214 IF( lower .AND. tmp1.GT.0 ) THEN
7215 CALL pb_slaset( 'All', m1, tmp1, 0, alpha, alpha,
7216 $ a( iia+(jja-1)*lda ), lda )
7217 jja = jja + tmp1
7218 n1 = n1 - tmp1
7219 END IF
7220*
7221 IF( nblks.LE.0 )
7222 $ RETURN
7223*
7224 lcmt = lcmt00
7225 nblkd = nblks
7226 joffd = joffa
7227*
7228 nbloc = nb
7229 40 CONTINUE
7230 IF( nblkd.GT.0 .AND. lcmt.LE.iupp ) THEN
7231 IF( nblkd.EQ.1 )
7232 $ nbloc = lnbloc
7233 CALL pb_slaset( uplo, imbloc, nbloc, lcmt, alpha, beta,
7234 $ a( iia+joffd*lda ), lda )
7235 lcmt00 = lcmt
7236 lcmt = lcmt + qnb
7237 nblks = nblkd
7238 nblkd = nblkd - 1
7239 joffa = joffd
7240 joffd = joffd + nbloc
7241 GO TO 40
7242 END IF
7243*
7244 tmp1 = n1 - joffd + jja - 1
7245 IF( upper .AND. tmp1.GT.0 )
7246 $ CALL pb_slaset( 'All', imbloc, tmp1, 0, alpha, alpha,
7247 $ a( iia+joffd*lda ), lda )
7248*
7249 tmp1 = joffa - jja + 1
7250 m1 = m1 - imbloc
7251 n1 = n1 - tmp1
7252 lcmt00 = lcmt00 - ( iupp - upp + pmb )
7253 mblks = mblks - 1
7254 ioffa = ioffa + imbloc
7255*
7256 IF( lower .AND. m1.GT.0 .AND. tmp1.GT.0 )
7257 $ CALL pb_slaset( 'All', m1, tmp1, 0, alpha, alpha,
7258 $ a( ioffa+1+(jja-1)*lda ), lda )
7259*
7260 iia = ioffa + 1
7261 jja = joffa + 1
7262*
7263 END IF
7264*
7265 nbloc = nb
7266 50 CONTINUE
7267 IF( nblks.GT.0 ) THEN
7268 IF( nblks.EQ.1 )
7269 $ nbloc = lnbloc
7270 60 CONTINUE
7271 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
7272 lcmt00 = lcmt00 - pmb
7273 mblks = mblks - 1
7274 ioffa = ioffa + mb
7275 GO TO 60
7276 END IF
7277*
7278 tmp1 = min( ioffa, iimax ) - iia + 1
7279 IF( upper .AND. tmp1.GT.0 ) THEN
7280 CALL pb_slaset( 'All', tmp1, n1, 0, alpha, alpha,
7281 $ a( iia+joffa*lda ), lda )
7282 iia = iia + tmp1
7283 m1 = m1 - tmp1
7284 END IF
7285*
7286 IF( mblks.LE.0 )
7287 $ RETURN
7288*
7289 lcmt = lcmt00
7290 mblkd = mblks
7291 ioffd = ioffa
7292*
7293 mbloc = mb
7294 70 CONTINUE
7295 IF( mblkd.GT.0 .AND. lcmt.GE.low ) THEN
7296 IF( mblkd.EQ.1 )
7297 $ mbloc = lmbloc
7298 CALL pb_slaset( uplo, mbloc, nbloc, lcmt, alpha, beta,
7299 $ a( ioffd+1+joffa*lda ), lda )
7300 lcmt00 = lcmt
7301 lcmt = lcmt - pmb
7302 mblks = mblkd
7303 mblkd = mblkd - 1
7304 ioffa = ioffd
7305 ioffd = ioffd + mbloc
7306 GO TO 70
7307 END IF
7308*
7309 tmp1 = m1 - ioffd + iia - 1
7310 IF( lower .AND. tmp1.GT.0 )
7311 $ CALL pb_slaset( 'All', tmp1, nbloc, 0, alpha, alpha,
7312 $ a( ioffd+1+joffa*lda ), lda )
7313*
7314 tmp1 = min( ioffa, iimax ) - iia + 1
7315 m1 = m1 - tmp1
7316 n1 = n1 - nbloc
7317 lcmt00 = lcmt00 + qnb
7318 nblks = nblks - 1
7319 joffa = joffa + nbloc
7320*
7321 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
7322 $ CALL pb_slaset( 'All', tmp1, n1, 0, alpha, alpha,
7323 $ a( iia+joffa*lda ), lda )
7324*
7325 iia = ioffa + 1
7326 jja = joffa + 1
7327*
7328 GO TO 50
7329*
7330 END IF
7331*
7332 RETURN
7333*
7334* End of PSLASET
7335*
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_slaset(uplo, m, n, ioffd, alpha, beta, a, lda)
Definition psblastst.f:9361
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: