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

◆ pdlaset()

subroutine pdlaset ( character*1  uplo,
integer  m,
integer  n,
double precision  alpha,
double precision  beta,
double precision, dimension( * )  a,
integer  ia,
integer  ja,
integer, dimension( * )  desca 
)

Definition at line 6861 of file pdblastst.f.

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