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

◆ pb_descinit2()

subroutine pb_descinit2 ( integer, dimension( * )  desc,
integer  m,
integer  n,
integer  imb,
integer  inb,
integer  mb,
integer  nb,
integer  rsrc,
integer  csrc,
integer  ctxt,
integer  lld,
integer  info 
)

Definition at line 3335 of file pblastst.f.

3337*
3338* -- PBLAS test routine (version 2.0) --
3339* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
3340* and University of California, Berkeley.
3341* April 1, 1998
3342*
3343* .. Scalar Arguments ..
3344 INTEGER CSRC, CTXT, IMB, INB, INFO, LLD, M, MB, N, NB,
3345 $ RSRC
3346* ..
3347* .. Array Arguments ..
3348 INTEGER DESC( * )
3349* ..
3350*
3351* Purpose
3352* =======
3353*
3354* PB_DESCINIT2 uses its 10 input arguments M, N, IMB, INB, MB, NB,
3355* RSRC, CSRC, CTXT and LLD to initialize a descriptor vector of type
3356* BLOCK_CYCLIC_2D_INB.
3357*
3358* Notes
3359* =====
3360*
3361* A description vector is associated with each 2D block-cyclicly dis-
3362* tributed matrix. This vector stores the information required to
3363* establish the mapping between a matrix entry and its corresponding
3364* process and memory location.
3365*
3366* In the following comments, the character _ should be read as
3367* "of the distributed matrix". Let A be a generic term for any 2D
3368* block cyclicly distributed matrix. Its description vector is DESCA:
3369*
3370* NOTATION STORED IN EXPLANATION
3371* ---------------- --------------- ------------------------------------
3372* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
3373* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
3374* the NPROW x NPCOL BLACS process grid
3375* A is distributed over. The context
3376* itself is global, but the handle
3377* (the integer value) may vary.
3378* M_A (global) DESCA( M_ ) The number of rows in the distribu-
3379* ted matrix A, M_A >= 0.
3380* N_A (global) DESCA( N_ ) The number of columns in the distri-
3381* buted matrix A, N_A >= 0.
3382* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
3383* block of the matrix A, IMB_A > 0.
3384* INB_A (global) DESCA( INB_ ) The number of columns of the upper
3385* left block of the matrix A,
3386* INB_A > 0.
3387* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
3388* bute the last M_A-IMB_A rows of A,
3389* MB_A > 0.
3390* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
3391* bute the last N_A-INB_A columns of
3392* A, NB_A > 0.
3393* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
3394* row of the matrix A is distributed,
3395* NPROW > RSRC_A >= 0.
3396* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
3397* first column of A is distributed.
3398* NPCOL > CSRC_A >= 0.
3399* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
3400* array storing the local blocks of
3401* the distributed matrix A,
3402* IF( Lc( 1, N_A ) > 0 )
3403* LLD_A >= MAX( 1, Lr( 1, M_A ) )
3404* ELSE
3405* LLD_A >= 1.
3406*
3407* Let K be the number of rows of a matrix A starting at the global in-
3408* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
3409* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
3410* receive if these K rows were distributed over NPROW processes. If K
3411* is the number of columns of a matrix A starting at the global index
3412* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
3413* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
3414* these K columns were distributed over NPCOL processes.
3415*
3416* The values of Lr() and Lc() may be determined via a call to the func-
3417* tion PB_NUMROC:
3418* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
3419* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
3420*
3421* Arguments
3422* =========
3423*
3424* DESC (global and local output) INTEGER array
3425* On entry, DESC is an array of dimension DLEN_. DESC is the
3426* array descriptor to be set.
3427*
3428* M (global input) INTEGER
3429* On entry, M specifies the number of rows of the matrix.
3430* M must be at least zero.
3431*
3432* N (global input) INTEGER
3433* On entry, N specifies the number of columns of the matrix.
3434* N must be at least zero.
3435*
3436* IMB (global input) INTEGER
3437* On entry, IMB specifies the row size of the first block of
3438* the global matrix distribution. IMB must be at least one.
3439*
3440* INB (global input) INTEGER
3441* On entry, INB specifies the column size of the first block
3442* of the global matrix distribution. INB must be at least one.
3443*
3444* MB (global input) INTEGER
3445* On entry, MB specifies the row size of the blocks used to
3446* partition the matrix. MB must be at least one.
3447*
3448* NB (global input) INTEGER
3449* On entry, NB specifies the column size of the blocks used to
3450* partition the matrix. NB must be at least one.
3451*
3452* RSRC (global input) INTEGER
3453* On entry, RSRC specifies the row coordinate of the process
3454* that possesses the first row of the matrix. When RSRC = -1,
3455* the data is not distributed but replicated, otherwise RSRC
3456* must be at least zero and strictly less than NPROW.
3457*
3458* CSRC (global input) INTEGER
3459* On entry, CSRC specifies the column coordinate of the pro-
3460* cess that possesses the first column of the matrix. When
3461* CSRC = -1, the data is not distributed but replicated, other-
3462* wise CSRC must be at least zero and strictly less than NPCOL.
3463*
3464* CTXT (local input) INTEGER
3465* On entry, CTXT specifies the BLACS context handle, indicating
3466* the global communication context. The value of the context
3467* itself is local.
3468*
3469* LLD (local input) INTEGER
3470* On entry, LLD specifies the leading dimension of the local
3471* array storing the local entries of the matrix. LLD must be at
3472* least MAX( 1, Lr(1,M) ).
3473*
3474* INFO (local output) INTEGER
3475* = 0: successful exit
3476* < 0: if INFO = -i, the i-th argument had an illegal value.
3477*
3478* Notes
3479* =====
3480*
3481* If the routine can recover from an erroneous input argument, it will
3482* return an acceptable descriptor vector. For example, if LLD = 0 on
3483* input, DESC( LLD_ ) will contain the smallest leading dimension re-
3484* quired to store the specified m by n matrix, INFO will however be set
3485* to -11 on exit in that case.
3486*
3487* -- Written on April 1, 1998 by
3488* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
3489*
3490* =====================================================================
3491*
3492* .. Parameters ..
3493 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
3494 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
3495 $ RSRC_
3496 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
3497 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
3498 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
3499 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
3500* ..
3501* .. Local Scalars ..
3502 INTEGER LLDMIN, MP, MYCOL, MYROW, NPCOL, NPROW
3503* ..
3504* .. External Subroutines ..
3505 EXTERNAL blacs_gridinfo, pxerbla
3506* ..
3507* .. External Functions ..
3508 INTEGER PB_NUMROC
3509 EXTERNAL pb_numroc
3510* ..
3511* .. Intrinsic Functions ..
3512 INTRINSIC max, min
3513* ..
3514* .. Executable Statements ..
3515*
3516* Get grid parameters
3517*
3518 CALL blacs_gridinfo( ctxt, nprow, npcol, myrow, mycol )
3519*
3520 info = 0
3521 IF( m.LT.0 ) THEN
3522 info = -2
3523 ELSE IF( n.LT.0 ) THEN
3524 info = -3
3525 ELSE IF( imb.LT.1 ) THEN
3526 info = -4
3527 ELSE IF( inb.LT.1 ) THEN
3528 info = -5
3529 ELSE IF( mb.LT.1 ) THEN
3530 info = -6
3531 ELSE IF( nb.LT.1 ) THEN
3532 info = -7
3533 ELSE IF( rsrc.LT.-1 .OR. rsrc.GE.nprow ) THEN
3534 info = -8
3535 ELSE IF( csrc.LT.-1 .OR. csrc.GE.npcol ) THEN
3536 info = -9
3537 ELSE IF( nprow.EQ.-1 ) THEN
3538 info = -10
3539 END IF
3540*
3541* Compute minimum LLD if safe (to avoid division by 0)
3542*
3543 IF( info.EQ.0 ) THEN
3544 mp = pb_numroc( m, 1, imb, mb, myrow, rsrc, nprow )
3545 IF( pb_numroc( n, 1, inb, nb, mycol, csrc, npcol ).GT.0 ) THEN
3546 lldmin = max( 1, mp )
3547 ELSE
3548 lldmin = 1
3549 END IF
3550 IF( lld.LT.lldmin )
3551 $ info = -11
3552 END IF
3553*
3554 IF( info.NE.0 )
3555 $ CALL pxerbla( ctxt, 'PB_DESCINIT2', -info )
3556*
3557 desc( dtype_ ) = block_cyclic_2d_inb
3558 desc( ctxt_ ) = ctxt
3559 desc( m_ ) = max( 0, m )
3560 desc( n_ ) = max( 0, n )
3561 desc( imb_ ) = max( 1, imb )
3562 desc( inb_ ) = max( 1, inb )
3563 desc( mb_ ) = max( 1, mb )
3564 desc( nb_ ) = max( 1, nb )
3565 desc( rsrc_ ) = max( -1, min( rsrc, nprow-1 ) )
3566 desc( csrc_ ) = max( -1, min( csrc, npcol-1 ) )
3567 desc( lld_ ) = max( lld, lldmin )
3568*
3569 RETURN
3570*
3571* End of PB_DESCINIT2
3572*
integer function pb_numroc(n, i, inb, nb, proc, srcproc, nprocs)
Definition pblastst.f:2548
#define max(A, B)
Definition pcgemr.c:180
#define min(A, B)
Definition pcgemr.c:181
subroutine pxerbla(ictxt, srname, info)
Definition pxerbla.f:2
Here is the caller graph for this function: