1      SUBROUTINE pslacon( N, V, IV, JV, DESCV, X, IX, JX, DESCX, ISGN,
 
   10      INTEGER            IV, IX, JV, JX, KASE, N
 
   14      INTEGER            DESCV( * ), DESCX( * ), ISGN( * )
 
  149      INTEGER            BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
 
  150     $                   lld_, mb_, m_, nb_, n_, rsrc_
 
  151      parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
 
  152     $                     ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
 
  153     $                     rsrc_ = 7, csrc_ = 8, lld_ = 9 )
 
  155      parameter( itmax = 5 )
 
  157      parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
 
  160      INTEGER            I, ICTXT, IFLAG, IIVX, IMAXROW, IOFFVX, IROFF,
 
  161     $                   iter, ivxcol, ivxrow, j, jlast, jjvx, jump,
 
  162     $                   k, mycol, myrow, np, npcol, nprow
 
  163      REAL               ALTSGN, ESTOLD, JLMAX, XMAX
 
  171      EXTERNAL           blacs_gridinfo, igsum2d, 
infog2l, psamax,
 
  176      INTEGER            INDXG2L, INDXG2P, INDXL2G, NUMROC
 
  177      EXTERNAL           indxg2l, indxg2p, indxl2g, numroc
 
  180      INTRINSIC          abs, mod, nint, real, sign
 
  190      ictxt = descx( ctxt_ )
 
  191      CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
 
  193      CALL infog2l( ix, jx, descx, nprow, npcol, myrow, mycol,
 
  194     $              iivx, jjvx, ivxrow, ivxcol )
 
  195      IF( mycol.NE.ivxcol )
 
  197      iroff = mod( ix-1, descx( mb_ ) )
 
  198      np = numroc( n+iroff, descx( mb_ ), myrow, ivxrow, nprow )
 
  199      IF( myrow.EQ.ivxrow )
 
  201      ioffvx = iivx + (jjvx-1)*descx( lld_ )
 
  204         DO 10 i = ioffvx, ioffvx+np-1
 
  205            x( i ) = one / real( n )
 
  212      GO TO ( 20, 40, 70, 110, 140 )jump
 
  219         IF( myrow.EQ.ivxrow ) 
THEN 
  220            v( ioffvx ) = x( ioffvx )
 
  221            estwork( 1 ) = abs( v( ioffvx ) )
 
  222            CALL sgebs2d( ictxt, 
'Columnwise', 
' ', 1, 1, estwork, 1 )
 
  224            CALL sgebr2d( ictxt, 
'Columnwise', 
' ', 1, 1, estwork, 1,
 
  230      CALL psasum( n, estwork( 1 ), x, ix, jx, descx, 1 )
 
  231      IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) 
THEN 
  232         IF( myrow.EQ.ivxrow ) 
THEN 
  233            CALL sgebs2d( ictxt, 
'Columnwise', 
' ', 1, 1, estwork, 1 )
 
  235            CALL sgebr2d( ictxt, 
'Columnwise', 
' ', 1, 1, estwork, 1,
 
  240      DO 30 i = ioffvx, ioffvx+np-1
 
  241         x( i ) = sign( one, x( i ) )
 
  242         isgn( i ) = nint( x( i ) )
 
  252      CALL psamax( n, xmax, j, x, ix, jx, descx, 1 )
 
  253      IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) 
THEN 
  254         IF( myrow.EQ.ivxrow ) 
THEN 
  256            work( 2 ) = real( j )
 
  257            CALL sgebs2d( ictxt, 
'Columnwise', 
' ', 2, 1, work, 2 )
 
  259            CALL sgebr2d( ictxt, 
'Columnwise', 
' ', 2, 1, work, 2,
 
  262            j = nint( work( 2 ) )
 
  270      DO 60 i = ioffvx, ioffvx+np-1
 
  273      imaxrow = indxg2p( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
 
  274      IF( myrow.EQ.imaxrow ) 
THEN 
  275         i = indxg2l( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
 
  286      CALL scopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
 
  287      estold = estwork( 1 )
 
  288      CALL psasum( n, estwork( 1 ), v, iv, jv, descv, 1 )
 
  289      IF( descv( m_ ).EQ.1 .AND. n.EQ.1 ) 
THEN 
  290         IF( myrow.EQ.ivxrow ) 
THEN 
  291            CALL sgebs2d( ictxt, 
'Columnwise', 
' ', 1, 1, estwork, 1 )
 
  293            CALL sgebr2d( ictxt, 
'Columnwise', 
' ', 1, 1, estwork, 1,
 
  298      DO 80 i = ioffvx, ioffvx+np-1
 
  299         IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) ) 
THEN 
  306      CALL igsum2d( ictxt, 
'C', 
' ', 1, 1, iflag, 1, -1, mycol )
 
  311      IF( iflag.EQ.0 .OR. estwork( 1 ).LE.estold )
 
  314      DO 100 i = ioffvx, ioffvx+np-1
 
  315         x( i ) = sign( one, x( i ) )
 
  316         isgn( i ) = nint( x( i ) )
 
  327      CALL psamax( n, xmax, j, x, ix, jx, descx, 1 )
 
  328      IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) 
THEN 
  329         IF( myrow.EQ.ivxrow ) 
THEN 
  331            work( 2 ) = real( j )
 
  332            CALL sgebs2d( ictxt, 
'Columnwise', 
' ', 2, 1, work, 2 )
 
  334            CALL sgebr2d( ictxt, 
'Columnwise', 
' ', 2, 1, work, 2,
 
  337            j = nint( work( 2 ) )
 
  340      CALL pselget( 
'Columnwise', 
' ', jlmax, x, jlast, jx, descx )
 
  341      IF( ( jlmax.NE.abs( xmax ) ).AND.( iter.LT.itmax ) ) 
THEN 
  349      DO 130 i = ioffvx, ioffvx+np-1
 
  350         k = indxl2g( i-ioffvx+iivx, descx( mb_ ), myrow,
 
  351     $                descx( rsrc_ ), nprow )-ix+1
 
  352         IF( mod( k, 2 ).EQ.0 ) 
THEN 
  357         x( i ) = altsgn*( one+real( k-1 ) / real( n-1 ) )
 
  367      CALL psasum( n, temp( 1 ), x, ix, jx, descx, 1 )
 
  368      IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) 
THEN 
  369         IF( myrow.EQ.ivxrow ) 
THEN 
  370            CALL sgebs2d( ictxt, 
'Columnwise', 
' ', 1, 1, temp, 1 )
 
  372            CALL sgebr2d( ictxt, 
'Columnwise', 
' ', 1, 1, temp, 1,
 
  376      temp( 1 ) = two*( temp( 1 ) / real( 3*n ) )
 
  377      IF( temp( 1 ).GT.estwork( 1 ) ) 
THEN 
  378         CALL scopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
 
  379         estwork( 1 ) = temp( 1 )