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

◆ pclascal()

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

Definition at line 7982 of file pcblastst.f.

7983*
7984* -- PBLAS test routine (version 2.0) --
7985* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
7986* and University of California, Berkeley.
7987* April 1, 1998
7988*
7989* .. Scalar Arguments ..
7990 CHARACTER*1 TYPE
7991 INTEGER IA, JA, M, N
7992 COMPLEX ALPHA
7993* ..
7994* .. Array Arguments ..
7995 INTEGER DESCA( * )
7996 COMPLEX A( * )
7997* ..
7998*
7999* Purpose
8000* =======
8001*
8002* PCLASCAL scales the m by n submatrix A(IA:IA+M-1,JA:JA+N-1) denoted
8003* by sub( A ) by the scalar alpha. TYPE specifies if sub( A ) is full,
8004* upper triangular, lower triangular or upper Hessenberg.
8005*
8006* Notes
8007* =====
8008*
8009* A description vector is associated with each 2D block-cyclicly dis-
8010* tributed matrix. This vector stores the information required to
8011* establish the mapping between a matrix entry and its corresponding
8012* process and memory location.
8013*
8014* In the following comments, the character _ should be read as
8015* "of the distributed matrix". Let A be a generic term for any 2D
8016* block cyclicly distributed matrix. Its description vector is DESCA:
8017*
8018* NOTATION STORED IN EXPLANATION
8019* ---------------- --------------- ------------------------------------
8020* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
8021* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
8022* the NPROW x NPCOL BLACS process grid
8023* A is distributed over. The context
8024* itself is global, but the handle
8025* (the integer value) may vary.
8026* M_A (global) DESCA( M_ ) The number of rows in the distribu-
8027* ted matrix A, M_A >= 0.
8028* N_A (global) DESCA( N_ ) The number of columns in the distri-
8029* buted matrix A, N_A >= 0.
8030* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
8031* block of the matrix A, IMB_A > 0.
8032* INB_A (global) DESCA( INB_ ) The number of columns of the upper
8033* left block of the matrix A,
8034* INB_A > 0.
8035* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
8036* bute the last M_A-IMB_A rows of A,
8037* MB_A > 0.
8038* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
8039* bute the last N_A-INB_A columns of
8040* A, NB_A > 0.
8041* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
8042* row of the matrix A is distributed,
8043* NPROW > RSRC_A >= 0.
8044* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
8045* first column of A is distributed.
8046* NPCOL > CSRC_A >= 0.
8047* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
8048* array storing the local blocks of
8049* the distributed matrix A,
8050* IF( Lc( 1, N_A ) > 0 )
8051* LLD_A >= MAX( 1, Lr( 1, M_A ) )
8052* ELSE
8053* LLD_A >= 1.
8054*
8055* Let K be the number of rows of a matrix A starting at the global in-
8056* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
8057* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
8058* receive if these K rows were distributed over NPROW processes. If K
8059* is the number of columns of a matrix A starting at the global index
8060* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
8061* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
8062* these K columns were distributed over NPCOL processes.
8063*
8064* The values of Lr() and Lc() may be determined via a call to the func-
8065* tion PB_NUMROC:
8066* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
8067* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
8068*
8069* Arguments
8070* =========
8071*
8072* TYPE (global input) CHARACTER*1
8073* On entry, TYPE specifies the type of the input submatrix as
8074* follows:
8075* = 'L' or 'l': sub( A ) is a lower triangular matrix,
8076* = 'U' or 'u': sub( A ) is an upper triangular matrix,
8077* = 'H' or 'h': sub( A ) is an upper Hessenberg matrix,
8078* otherwise sub( A ) is a full matrix.
8079*
8080* M (global input) INTEGER
8081* On entry, M specifies the number of rows of the submatrix
8082* sub( A ). M must be at least zero.
8083*
8084* N (global input) INTEGER
8085* On entry, N specifies the number of columns of the submatrix
8086* sub( A ). N must be at least zero.
8087*
8088* ALPHA (global input) COMPLEX
8089* On entry, ALPHA specifies the scalar alpha.
8090*
8091* A (local input/local output) COMPLEX array
8092* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
8093* at least Lc( 1, JA+N-1 ). Before entry, this array contains
8094* the local entries of the matrix A.
8095* On exit, the local entries of this array corresponding to the
8096* to the entries of the submatrix sub( A ) are overwritten by
8097* the local entries of the m by n scaled submatrix.
8098*
8099* IA (global input) INTEGER
8100* On entry, IA specifies A's global row index, which points to
8101* the beginning of the submatrix sub( A ).
8102*
8103* JA (global input) INTEGER
8104* On entry, JA specifies A's global column index, which points
8105* to the beginning of the submatrix sub( A ).
8106*
8107* DESCA (global and local input) INTEGER array
8108* On entry, DESCA is an integer array of dimension DLEN_. This
8109* is the array descriptor for the matrix A.
8110*
8111* -- Written on April 1, 1998 by
8112* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
8113*
8114* =====================================================================
8115*
8116* .. Parameters ..
8117 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
8118 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
8119 $ RSRC_
8120 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
8121 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
8122 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
8123 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
8124* ..
8125* .. Local Scalars ..
8126 CHARACTER*1 UPLO
8127 LOGICAL GODOWN, GOLEFT, LOWER, UPPER
8128 INTEGER IACOL, IAROW, ICTXT, IIA, IIMAX, ILOW, IMB1,
8129 $ IMBLOC, INB1, INBLOC, IOFFA, IOFFD, ITYPE,
8130 $ IUPP, JJA, JJMAX, JOFFA, JOFFD, LCMT, LCMT00,
8131 $ LDA, LMBLOC, LNBLOC, LOW, M1, MB, MBLKD, MBLKS,
8132 $ MBLOC, MP, MRCOL, MRROW, MYCOL, MYROW, N1, NB,
8133 $ NBLKD, NBLKS, NBLOC, NPCOL, NPROW, NQ, PMB,
8134 $ QNB, TMP1, UPP
8135* ..
8136* .. Local Arrays ..
8137 INTEGER DESCA2( DLEN_ )
8138* ..
8139* .. External Subroutines ..
8140 EXTERNAL blacs_gridinfo, pb_ainfog2l, pb_binfo,
8142* ..
8143* .. External Functions ..
8144 LOGICAL LSAME
8145 INTEGER PB_NUMROC
8146 EXTERNAL lsame, pb_numroc
8147* ..
8148* .. Intrinsic Functions ..
8149 INTRINSIC min
8150* ..
8151* .. Executable Statements ..
8152*
8153* Convert descriptor
8154*
8155 CALL pb_desctrans( desca, desca2 )
8156*
8157* Get grid parameters
8158*
8159 ictxt = desca2( ctxt_ )
8160 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
8161*
8162* Quick return if possible
8163*
8164 IF( m.EQ.0 .OR. n.EQ.0 )
8165 $ RETURN
8166*
8167 IF( lsame( TYPE, 'L' ) ) THEN
8168 itype = 1
8169 uplo = TYPE
8170 upper = .false.
8171 lower = .true.
8172 ioffd = 0
8173 ELSE IF( lsame( TYPE, 'U' ) ) THEN
8174 itype = 2
8175 uplo = TYPE
8176 upper = .true.
8177 lower = .false.
8178 ioffd = 0
8179 ELSE IF( lsame( TYPE, 'H' ) ) THEN
8180 itype = 3
8181 uplo = 'U'
8182 upper = .true.
8183 lower = .false.
8184 ioffd = 1
8185 ELSE
8186 itype = 0
8187 uplo = 'A'
8188 upper = .true.
8189 lower = .true.
8190 ioffd = 0
8191 END IF
8192*
8193* Compute local indexes
8194*
8195 IF( itype.EQ.0 ) THEN
8196*
8197* Full matrix
8198*
8199 CALL pb_infog2l( ia, ja, desca2, nprow, npcol, myrow, mycol,
8200 $ iia, jja, iarow, iacol )
8201 mp = pb_numroc( m, ia, desca2( imb_ ), desca2( mb_ ), myrow,
8202 $ desca2( rsrc_ ), nprow )
8203 nq = pb_numroc( n, ja, desca2( inb_ ), desca2( nb_ ), mycol,
8204 $ desca2( csrc_ ), npcol )
8205*
8206 IF( mp.LE.0 .OR. nq.LE.0 )
8207 $ RETURN
8208*
8209 lda = desca2( lld_ )
8210 ioffa = iia + ( jja - 1 ) * lda
8211*
8212 CALL pb_clascal( 'All', mp, nq, 0, alpha, a( ioffa ), lda )
8213*
8214 ELSE
8215*
8216* Trapezoidal matrix
8217*
8218 CALL pb_ainfog2l( m, n, ia, ja, desca2, nprow, npcol, myrow,
8219 $ mycol, imb1, inb1, mp, nq, iia, jja, iarow,
8220 $ iacol, mrrow, mrcol )
8221*
8222 IF( mp.LE.0 .OR. nq.LE.0 )
8223 $ RETURN
8224*
8225* Initialize LCMT00, MBLKS, NBLKS, IMBLOC, INBLOC, LMBLOC,
8226* LNBLOC, ILOW, LOW, IUPP, and UPP.
8227*
8228 mb = desca2( mb_ )
8229 nb = desca2( nb_ )
8230 lda = desca2( lld_ )
8231*
8232 CALL pb_binfo( ioffd, mp, nq, imb1, inb1, mb, nb, mrrow,
8233 $ mrcol, lcmt00, mblks, nblks, imbloc, inbloc,
8234 $ lmbloc, lnbloc, ilow, low, iupp, upp )
8235*
8236 m1 = mp
8237 n1 = nq
8238 ioffa = iia - 1
8239 joffa = jja - 1
8240 iimax = ioffa + mp
8241 jjmax = joffa + nq
8242*
8243 IF( desca2( rsrc_ ).LT.0 ) THEN
8244 pmb = mb
8245 ELSE
8246 pmb = nprow * mb
8247 END IF
8248 IF( desca2( csrc_ ).LT.0 ) THEN
8249 qnb = nb
8250 ELSE
8251 qnb = npcol * nb
8252 END IF
8253*
8254* Handle the first block of rows or columns separately, and
8255* update LCMT00, MBLKS and NBLKS.
8256*
8257 godown = ( lcmt00.GT.iupp )
8258 goleft = ( lcmt00.LT.ilow )
8259*
8260 IF( .NOT.godown .AND. .NOT.goleft ) THEN
8261*
8262* LCMT00 >= ILOW && LCMT00 <= IUPP
8263*
8264 goleft = ( ( lcmt00 - ( iupp - upp + pmb ) ).LT.ilow )
8265 godown = .NOT.goleft
8266*
8267 CALL pb_clascal( uplo, imbloc, inbloc, lcmt00, alpha,
8268 $ a( iia+joffa*lda ), lda )
8269 IF( godown ) THEN
8270 IF( upper .AND. nq.GT.inbloc )
8271 $ CALL pb_clascal( 'All', imbloc, nq-inbloc, 0, alpha,
8272 $ a( iia+(joffa+inbloc)*lda ), lda )
8273 iia = iia + imbloc
8274 m1 = m1 - imbloc
8275 ELSE
8276 IF( lower .AND. mp.GT.imbloc )
8277 $ CALL pb_clascal( 'All', mp-imbloc, inbloc, 0, alpha,
8278 $ a( iia+imbloc+joffa*lda ), lda )
8279 jja = jja + inbloc
8280 n1 = n1 - inbloc
8281 END IF
8282*
8283 END IF
8284*
8285 IF( godown ) THEN
8286*
8287 lcmt00 = lcmt00 - ( iupp - upp + pmb )
8288 mblks = mblks - 1
8289 ioffa = ioffa + imbloc
8290*
8291 10 CONTINUE
8292 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
8293 lcmt00 = lcmt00 - pmb
8294 mblks = mblks - 1
8295 ioffa = ioffa + mb
8296 GO TO 10
8297 END IF
8298*
8299 tmp1 = min( ioffa, iimax ) - iia + 1
8300 IF( upper .AND. tmp1.GT.0 ) THEN
8301 CALL pb_clascal( 'All', tmp1, n1, 0, alpha,
8302 $ a( iia+joffa*lda ), lda )
8303 iia = iia + tmp1
8304 m1 = m1 - tmp1
8305 END IF
8306*
8307 IF( mblks.LE.0 )
8308 $ RETURN
8309*
8310 lcmt = lcmt00
8311 mblkd = mblks
8312 ioffd = ioffa
8313*
8314 mbloc = mb
8315 20 CONTINUE
8316 IF( mblkd.GT.0 .AND. lcmt.GE.ilow ) THEN
8317 IF( mblkd.EQ.1 )
8318 $ mbloc = lmbloc
8319 CALL pb_clascal( uplo, mbloc, inbloc, lcmt, alpha,
8320 $ a( ioffd+1+joffa*lda ), lda )
8321 lcmt00 = lcmt
8322 lcmt = lcmt - pmb
8323 mblks = mblkd
8324 mblkd = mblkd - 1
8325 ioffa = ioffd
8326 ioffd = ioffd + mbloc
8327 GO TO 20
8328 END IF
8329*
8330 tmp1 = m1 - ioffd + iia - 1
8331 IF( lower .AND. tmp1.GT.0 )
8332 $ CALL pb_clascal( 'All', tmp1, inbloc, 0, alpha,
8333 $ a( ioffd+1+joffa*lda ), lda )
8334*
8335 tmp1 = ioffa - iia + 1
8336 m1 = m1 - tmp1
8337 n1 = n1 - inbloc
8338 lcmt00 = lcmt00 + low - ilow + qnb
8339 nblks = nblks - 1
8340 joffa = joffa + inbloc
8341*
8342 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
8343 $ CALL pb_clascal( 'All', tmp1, n1, 0, alpha,
8344 $ a( iia+joffa*lda ), lda )
8345*
8346 iia = ioffa + 1
8347 jja = joffa + 1
8348*
8349 ELSE IF( goleft ) THEN
8350*
8351 lcmt00 = lcmt00 + low - ilow + qnb
8352 nblks = nblks - 1
8353 joffa = joffa + inbloc
8354*
8355 30 CONTINUE
8356 IF( nblks.GT.0 .AND. lcmt00.LT.low ) THEN
8357 lcmt00 = lcmt00 + qnb
8358 nblks = nblks - 1
8359 joffa = joffa + nb
8360 GO TO 30
8361 END IF
8362*
8363 tmp1 = min( joffa, jjmax ) - jja + 1
8364 IF( lower .AND. tmp1.GT.0 ) THEN
8365 CALL pb_clascal( 'All', m1, tmp1, 0, alpha,
8366 $ a( iia+(jja-1)*lda ), lda )
8367 jja = jja + tmp1
8368 n1 = n1 - tmp1
8369 END IF
8370*
8371 IF( nblks.LE.0 )
8372 $ RETURN
8373*
8374 lcmt = lcmt00
8375 nblkd = nblks
8376 joffd = joffa
8377*
8378 nbloc = nb
8379 40 CONTINUE
8380 IF( nblkd.GT.0 .AND. lcmt.LE.iupp ) THEN
8381 IF( nblkd.EQ.1 )
8382 $ nbloc = lnbloc
8383 CALL pb_clascal( uplo, imbloc, nbloc, lcmt, alpha,
8384 $ a( iia+joffd*lda ), lda )
8385 lcmt00 = lcmt
8386 lcmt = lcmt + qnb
8387 nblks = nblkd
8388 nblkd = nblkd - 1
8389 joffa = joffd
8390 joffd = joffd + nbloc
8391 GO TO 40
8392 END IF
8393*
8394 tmp1 = n1 - joffd + jja - 1
8395 IF( upper .AND. tmp1.GT.0 )
8396 $ CALL pb_clascal( 'All', imbloc, tmp1, 0, alpha,
8397 $ a( iia+joffd*lda ), lda )
8398*
8399 tmp1 = joffa - jja + 1
8400 m1 = m1 - imbloc
8401 n1 = n1 - tmp1
8402 lcmt00 = lcmt00 - ( iupp - upp + pmb )
8403 mblks = mblks - 1
8404 ioffa = ioffa + imbloc
8405*
8406 IF( lower .AND. m1.GT.0 .AND. tmp1.GT.0 )
8407 $ CALL pb_clascal( 'All', m1, tmp1, 0, alpha,
8408 $ a( ioffa+1+(jja-1)*lda ), lda )
8409*
8410 iia = ioffa + 1
8411 jja = joffa + 1
8412*
8413 END IF
8414*
8415 nbloc = nb
8416 50 CONTINUE
8417 IF( nblks.GT.0 ) THEN
8418 IF( nblks.EQ.1 )
8419 $ nbloc = lnbloc
8420 60 CONTINUE
8421 IF( mblks.GT.0 .AND. lcmt00.GT.upp ) THEN
8422 lcmt00 = lcmt00 - pmb
8423 mblks = mblks - 1
8424 ioffa = ioffa + mb
8425 GO TO 60
8426 END IF
8427*
8428 tmp1 = min( ioffa, iimax ) - iia + 1
8429 IF( upper .AND. tmp1.GT.0 ) THEN
8430 CALL pb_clascal( 'All', tmp1, n1, 0, alpha,
8431 $ a( iia+joffa*lda ), lda )
8432 iia = iia + tmp1
8433 m1 = m1 - tmp1
8434 END IF
8435*
8436 IF( mblks.LE.0 )
8437 $ RETURN
8438*
8439 lcmt = lcmt00
8440 mblkd = mblks
8441 ioffd = ioffa
8442*
8443 mbloc = mb
8444 70 CONTINUE
8445 IF( mblkd.GT.0 .AND. lcmt.GE.low ) THEN
8446 IF( mblkd.EQ.1 )
8447 $ mbloc = lmbloc
8448 CALL pb_clascal( uplo, mbloc, nbloc, lcmt, alpha,
8449 $ a( ioffd+1+joffa*lda ), lda )
8450 lcmt00 = lcmt
8451 lcmt = lcmt - pmb
8452 mblks = mblkd
8453 mblkd = mblkd - 1
8454 ioffa = ioffd
8455 ioffd = ioffd + mbloc
8456 GO TO 70
8457 END IF
8458*
8459 tmp1 = m1 - ioffd + iia - 1
8460 IF( lower .AND. tmp1.GT.0 )
8461 $ CALL pb_clascal( 'All', tmp1, nbloc, 0, alpha,
8462 $ a( ioffd+1+joffa*lda ), lda )
8463*
8464 tmp1 = min( ioffa, iimax ) - iia + 1
8465 m1 = m1 - tmp1
8466 n1 = n1 - nbloc
8467 lcmt00 = lcmt00 + qnb
8468 nblks = nblks - 1
8469 joffa = joffa + nbloc
8470*
8471 IF( upper .AND. tmp1.GT.0 .AND. n1.GT.0 )
8472 $ CALL pb_clascal( 'All', tmp1, n1, 0, alpha,
8473 $ a( iia+joffa*lda ), lda )
8474*
8475 iia = ioffa + 1
8476 jja = joffa + 1
8477*
8478 GO TO 50
8479*
8480 END IF
8481*
8482 END IF
8483*
8484 RETURN
8485*
8486* End of PCLASCAL
8487*
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
subroutine pb_clascal(uplo, m, n, ioffd, alpha, a, lda)
#define min(A, B)
Definition pcgemr.c:181
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: