1      SUBROUTINE pselget( SCOPE, TOP, ALPHA, A, IA, JA, DESCA )
 
  115      INTEGER            BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
 
  116     $                   LLD_, MB_, M_, NB_, N_, RSRC_
 
  117      parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
 
  118     $                     ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
 
  119     $                     rsrc_ = 7, csrc_ = 8, lld_ = 9 )
 
  121      parameter( zero = 0.0e+0 )
 
  124      INTEGER            IACOL, IAROW, ICTXT, IIA, IOFFA, JJA, MYCOL,
 
  125     $                   MYROW, NPCOL, NPROW
 
  128      EXTERNAL           blacs_gridinfo, 
infog2l, sgebr2d, sgebs2d
 
  138      ictxt = desca( ctxt_ )
 
  139      CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
 
  141      CALL infog2l( ia, ja, desca, nprow, npcol, myrow, mycol, iia, jja,
 
  146      IF( lsame( scope, 
'R' ) ) 
THEN 
  147         IF( myrow.EQ.iarow ) 
THEN 
  148            IF( mycol.EQ.iacol ) 
THEN 
  149               ioffa = iia+(jja-1)*desca( lld_ )
 
  150               CALL sgebs2d( ictxt, scope, top, 1, 1, a( ioffa ), 1 )
 
  153               CALL sgebr2d( ictxt, scope, top, 1, 1, alpha, 1,
 
  157      ELSE IF( lsame( scope, 
'C' ) ) 
THEN 
  158         IF( mycol.EQ.iacol ) 
THEN 
  159            IF( myrow.EQ.iarow ) 
THEN 
  160               ioffa = iia+(jja-1)*desca( lld_ )
 
  161               CALL sgebs2d( ictxt, scope, top, 1, 1, a( ioffa ), 1 )
 
  164               CALL sgebr2d( ictxt, scope, top, 1, 1, alpha, 1,
 
  168      ELSE IF( lsame( scope, 
'A' ) ) 
THEN 
  169         IF( ( myrow.EQ.iarow ).AND.( mycol.EQ.iacol ) ) 
THEN 
  170            ioffa = iia+(jja-1)*desca( lld_ )
 
  171            CALL sgebs2d( ictxt, scope, top, 1, 1, a( ioffa ), 1 )
 
  174            CALL sgebr2d( ictxt, scope, top, 1, 1, alpha, 1,
 
  178         IF( myrow.EQ.iarow .AND. mycol.EQ.iacol )
 
  179     $      alpha = a( iia+(jja-1)*desca( lld_ ) )
 
 
subroutine infog2l(grindx, gcindx, desc, nprow, npcol, myrow, mycol, lrindx, lcindx, rsrc, csrc)