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

◆ pzlascal()

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

Definition at line 7983 of file pzblastst.f.

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