1      SUBROUTINE psgerfs( TRANS, N, NRHS, A, IA, JA, DESCA, AF, IAF,
 
    2     $                    JAF, DESCAF, IPIV, B, IB, JB, DESCB, X, IX,
 
    3     $                    JX, DESCX, FERR, BERR, WORK, LWORK, IWORK,
 
   13      INTEGER            IA, IAF, IB, IX, INFO, JA, JAF, JB, JX,
 
   14     $                   LIWORK, LWORK, N, NRHS
 
   17      INTEGER            DESCA( * ), DESCAF( * ), DESCB( * ),
 
   18     $                   DESCX( * ),IPIV( * ), IWORK( * )
 
   19      REAL               A( * ), AF( * ), B( * ), BERR( * ), FERR( * ),
 
  261      INTEGER            BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
 
  262     $                   LLD_, MB_, M_, NB_, N_, RSRC_
 
  263      PARAMETER          ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
 
  264     $                     ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
 
  265     $                     rsrc_ = 7, csrc_ = 8, lld_ = 9 )
 
  267      PARAMETER          ( ITMAX = 5 )
 
  269      parameter( zero = 0.0e+0, one = 1.0e+0 )
 
  271      parameter( two = 2.0e+0, three = 3.0e+0 )
 
  274      LOGICAL            LQUERY, NOTRAN
 
  276      INTEGER            COUNT, IACOL, IAFCOL, IAFROW, IAROW, IXBCOL,
 
  277     $                   ixbrow, ixcol, ixrow, icoffa, icoffaf, icoffb,
 
  278     $                   icoffx, ictxt, icurcol, idum, ii, iixb, iiw,
 
  279     $                   ioffxb, ipb, ipr, ipv, iroffa, iroffaf, iroffb,
 
  280     $                   iroffx, iw, j, jbrhs, jj, jjfbe, jjxb, jn, jw,
 
  281     $                   k, kase, ldxb, liwmin, lwmin, mycol, myrhs,
 
  282     $                   myrow, np, np0, npcol, npmod, nprow, nz
 
  283      REAL               EPS, EST, LSTRES, S, SAFE1, SAFE2, SAFMIN
 
  286      INTEGER            DESCW( DLEN_ ), IDUM1( 5 ), IDUM2( 5 )
 
  290      INTEGER            ICEIL, INDXG2P, NUMROC
 
  292      EXTERNAL           iceil, indxg2p, lsame, numroc, pslamch
 
  296     $                   
pchk2mat, psagemv, psaxpy, pscopy,
 
  298     $                   sgamx2d, sgebr2d, sgebs2d
 
  301      INTRINSIC          abs, ichar, 
max, 
min, mod, real
 
  307      ictxt = desca( ctxt_ )
 
  308      CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
 
  312      notran = lsame( trans, 
'N' )
 
  315      IF( nprow.EQ.-1 ) 
THEN 
  318         CALL chk1mat( n, 2, n, 2, ia, ja, desca, 7, info )
 
  319         CALL chk1mat( n, 2, n, 2, iaf, jaf, descaf, 11, info )
 
  320         CALL chk1mat( n, 2, nrhs, 3, ib, jb, descb, 16, info )
 
  321         CALL chk1mat( n, 2, nrhs, 3, ix, jx, descx, 20, info )
 
  323            iroffa = mod( ia-1, desca( mb_ ) )
 
  324            icoffa = mod( ja-1, desca( nb_ ) )
 
  325            iroffaf = mod( iaf-1, descaf( mb_ ) )
 
  326            icoffaf = mod( jaf-1, descaf( nb_ ) )
 
  327            iroffb = mod( ib-1, descb( mb_ ) )
 
  328            icoffb = mod( jb-1, descb( nb_ ) )
 
  329            iroffx = mod( ix-1, descx( mb_ ) )
 
  330            icoffx = mod( jx-1, descx( nb_ ) )
 
  331            iarow = indxg2p( ia, desca( mb_ ), myrow, desca( rsrc_ ),
 
  333            iafcol = indxg2p( jaf, descaf( nb_ ), mycol,
 
  334     $                        descaf( csrc_ ), npcol )
 
  335            iafrow = indxg2p( iaf, descaf( mb_ ), myrow,
 
  336     $                        descaf( rsrc_ ), nprow )
 
  337            iacol = indxg2p( ja, desca( nb_ ), mycol, desca( csrc_ ),
 
  339            CALL infog2l( ib, jb, descb, nprow, npcol, myrow, mycol,
 
  340     $                    iixb, jjxb, ixbrow, ixbcol )
 
  341            ixrow = indxg2p( ix, descx( mb_ ), myrow, descx( rsrc_ ),
 
  343            ixcol = indxg2p( jx, descx( nb_ ), mycol, descx( csrc_ ),
 
  345            npmod = numroc( n+iroffa, desca( mb_ ), myrow, iarow,
 
  349            work( 1 ) = real( lwmin )
 
  351            lquery = ( lwork.EQ.-1 .OR. liwork.EQ.-1 )
 
  353            IF( ( .NOT.notran ) .AND. ( .NOT.lsame( trans, 
'T' ) ) .AND.
 
  354     $          ( .NOT.lsame( trans, 
'C' ) ) ) 
THEN 
  356            ELSE IF( n.LT.0 ) 
THEN 
  358            ELSE IF( nrhs.LT.0 ) 
THEN 
  360            ELSE IF( iroffa.NE.0 ) 
THEN 
  362            ELSE IF( icoffa.NE.0 ) 
THEN 
  364            ELSE IF( desca( mb_ ).NE.desca( nb_ ) ) 
THEN 
  365               info = -( 700 + nb_ )
 
  366            ELSE IF( desca( mb_ ).NE.descaf( mb_ ) ) 
THEN 
  367               info = -( 1100 + mb_ )
 
  368            ELSE IF( iroffaf.NE.0 .OR. iarow.NE.iafrow ) 
THEN 
  370            ELSE IF( desca( nb_ ).NE.descaf( nb_ ) ) 
THEN 
  371               info = -( 1100 + nb_ )
 
  372            ELSE IF( icoffaf.NE.0 .OR. iacol.NE.iafcol ) 
THEN 
  374            ELSE IF( ictxt.NE.descaf( ctxt_ ) ) 
THEN 
  375               info = -( 1100 + ctxt_ )
 
  376            ELSE IF( iroffa.NE.iroffb .OR. iarow.NE.ixbrow ) 
THEN 
  378            ELSE IF( desca( mb_ ).NE.descb( mb_ ) ) 
THEN 
  379               info = -( 1600 + mb_ )
 
  380            ELSE IF( ictxt.NE.descb( ctxt_ ) ) 
THEN 
  381               info = -( 1600 + ctxt_ )
 
  382            ELSE IF( descb( mb_ ).NE.descx( mb_ ) ) 
THEN 
  383               info = -( 2000 + mb_ )
 
  384            ELSE IF( iroffx.NE.0 .OR. ixbrow.NE.ixrow ) 
THEN 
  386            ELSE IF( descb( nb_ ).NE.descx( nb_ ) ) 
THEN 
  387               info = -( 2000 + nb_ )
 
  388            ELSE IF( icoffb.NE.icoffx .OR. ixbcol.NE.ixcol ) 
THEN 
  390            ELSE IF( ictxt.NE.descx( ctxt_ ) ) 
THEN 
  391               info = -( 2000 + ctxt_ )
 
  392            ELSE IF( lwork.LT.lwmin .AND. .NOT.lquery ) 
THEN 
  394            ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) 
THEN 
  400            idum1( 1 ) = ichar( 
'N' )
 
  401         ELSE IF( lsame( trans, 
'T' ) ) 
THEN 
  402            idum1( 1 ) = ichar( 
'T' )
 
  404            idum1( 1 ) = ichar( 
'C' )
 
  411         IF( lwork.EQ.-1 ) 
THEN 
  417         IF( liwork.EQ.-1 ) 
THEN 
  423         CALL pchk2mat( n, 2, n, 2, ia, ja, desca, 7, n, 2, n, 2, iaf,
 
  424     $                  jaf, descaf, 11, 5, idum1, idum2, info )
 
  425         CALL pchk2mat( n, 2, nrhs, 3, ib, jb, descb, 16, n, 2, nrhs, 3,
 
  426     $                  ix, jx, descx, 20, 5, idum1, idum2, info )
 
  429         CALL pxerbla( ictxt, 
'PSGERFS', -info )
 
  431      ELSE IF( lquery ) 
THEN 
  436      myrhs = numroc( jb+nrhs-1, descb( nb_ ), mycol, descb( csrc_ ),
 
  441      IF( n.LE.1 .OR. nrhs.EQ.0 ) 
THEN 
  442         DO 10 jj = jjfbe, myrhs
 
  455      np0 = numroc( n+iroffb, descb( mb_ ), myrow, ixbrow, nprow )
 
  456      CALL descset( descw, n+iroffb, 1, desca( mb_ ), 1, ixbrow, ixbcol,
 
  457     $              ictxt, 
max( 1, np0 ) )
 
  461      IF( myrow.EQ.ixbrow ) 
THEN 
  471      ioffxb = ( jjxb-1 )*ldxb
 
  476      eps = pslamch( ictxt, 
'Epsilon' )
 
  477      safmin = pslamch( ictxt, 
'Safe minimum' )
 
  480      jn = 
min( iceil( jb, descb( nb_ ) ) * descb( nb_ ), jb+nrhs-1 )
 
  485      DO 100 k = 0, jbrhs-1
 
  497         CALL pscopy( n, b, ib, jb+k, descb, 1, work( ipr ), iw, jw,
 
  499         CALL psgemv( trans, n, n, -one, a, ia, ja, desca, x, ix,
 
  500     $                jx+k, descx, 1, one, work( ipr ), iw, jw,
 
  513         IF( mycol.EQ.ixbcol ) 
THEN 
  515               DO 30 ii = iixb, iixb + np - 1
 
  516                  work( iiw+ii-iixb ) = abs( b( ii+ioffxb ) )
 
  521         CALL psagemv( trans, n, n, one, a, ia, ja, desca, x, ix, jx+k,
 
  522     $                 descx, 1, one, work( ipb ), iw, jw, descw, 1 )
 
  525         IF( mycol.EQ.ixbcol ) 
THEN 
  527               DO 40 ii = iiw-1, iiw+np-2
 
  528                  IF( work( ipb+ii ).GT.safe2 ) 
THEN 
  529                     s = 
max( s, abs( work( ipr+ii ) ) /
 
  532                     s = 
max( s, ( abs( work( ipr+ii ) )+safe1 ) /
 
  533     $                           ( work( ipb+ii )+safe1 ) )
 
  539         CALL sgamx2d( ictxt, 
'All', 
' ', 1, 1, s, 1, idum, idum, 1,
 
  541         IF( mycol.EQ.ixbcol )
 
  551         IF( s.GT.eps .AND. two*s.LE.lstres .AND. count.LE.itmax ) 
THEN 
  555            CALL psgetrs( trans, n, 1, af, iaf, jaf, descaf, ipiv,
 
  556     $                    work( ipr ), iw, jw, descw, info )
 
  557            CALL psaxpy( n, one, work( ipr ), iw, jw, descw, 1, x, ix,
 
  590         IF( mycol.EQ.ixbcol ) 
THEN 
  592               DO 50 ii = iiw-1, iiw+np-2
 
  593                  IF( work( ipb+ii ).GT.safe2 ) 
THEN 
  594                     work( ipb+ii ) = abs( work( ipr+ii ) ) +
 
  595     $                                nz*eps*work( ipb+ii )
 
  597                     work( ipb+ii ) = abs( work( ipr+ii ) ) +
 
  598     $                                nz*eps*work( ipb+ii ) + safe1
 
  606         IF( mycol.EQ.ixbcol ) 
THEN 
  607            CALL sgebs2d( ictxt, 
'Rowwise', 
' ', np, 1, work( ipr ),
 
  610            CALL sgebr2d( ictxt, 
'Rowwise', 
' ', np, 1, work( ipr ),
 
  611     $                    descw( lld_ ), myrow, ixbcol )
 
  613         descw( csrc_ ) = mycol
 
  614         CALL pslacon( n, work( ipv ), iw, jw, descw, work( ipr ),
 
  615     $                 iw, jw, descw, iwork, est, kase )
 
  616         descw( csrc_ ) = ixbcol
 
  623               CALL psgetrs( transt, n, 1, af, iaf, jaf, descaf,
 
  624     $                       ipiv, work( ipr ), iw, jw, descw, info )
 
  626               IF( mycol.EQ.ixbcol ) 
THEN 
  628                     DO 70 ii = iiw-1, iiw+np-2
 
  629                        work( ipr+ii ) = work( ipb+ii )*work( ipr+ii )
 
  637               IF( mycol.EQ.ixbcol ) 
THEN 
  639                     DO 80 ii = iiw-1, iiw+np-2
 
  640                        work( ipr+ii ) = work( ipb+ii )*work( ipr+ii )
 
  645               CALL psgetrs( trans, n, 1, af, iaf, jaf, descaf, ipiv,
 
  646     $                       work( ipr ), iw, jw, descw, info )
 
  654         IF( mycol.EQ.ixbcol ) 
THEN 
  656               DO 90 ii = iixb, iixb+np-1
 
  657                  lstres = 
max( lstres, abs( x( ioffxb+ii ) ) )
 
  660            CALL sgamx2d( ictxt, 
'Column', 
' ', 1, 1, lstres, 1, idum,
 
  661     $                    idum, 1, -1, mycol )
 
  663     $         ferr( jjfbe ) = est / lstres
 
  667            ioffxb = ioffxb + ldxb
 
  673      icurcol = mod( ixbcol+1, npcol )
 
  677      DO 200 j = jn+1, jb+nrhs-1, descb( nb_ )
 
  678         jbrhs = 
min( jb+nrhs-j, descb( nb_ ) )
 
  679         descw( csrc_ ) = icurcol
 
  681         DO 190 k = 0, jbrhs-1
 
  693            CALL pscopy( n, b, ib, j+k, descb, 1, work( ipr ), iw, jw,
 
  695            CALL psgemv( trans, n, n, -one, a, ia, ja, desca, x,
 
  696     $                   ix, j+k, descx, 1, one, work( ipr ), iw, jw,
 
  710            IF( mycol.EQ.icurcol ) 
THEN 
  712                  DO 120 ii = iixb, iixb+np-1
 
  713                     work( iiw+ii-iixb ) = abs( b( ii+ioffxb ) )
 
  718            CALL psagemv( trans, n, n, one, a, ia, ja, desca, x, ix,
 
  719     $                    j+k, descx, 1, one, work( ipb ), iw, jw,
 
  723            IF( mycol.EQ.icurcol ) 
THEN 
  725                  DO 130 ii = iiw-1, iiw+np-2
 
  726                     IF( work( ipb+ii ).GT.safe2 ) 
THEN 
  727                        s = 
max( s, abs( work( ipr+ii ) ) /
 
  730                        s = 
max( s, ( abs( work( ipr+ii ) )+safe1 ) /
 
  731     $                              ( work( ipb+ii )+safe1 ) )
 
  737            CALL sgamx2d( ictxt, 
'All', 
' ', 1, 1, s, 1, idum, idum, 1,
 
  739            IF( mycol.EQ.icurcol )
 
  749            IF( s.GT.eps .AND. two*s.LE.lstres .AND.
 
  750     $          count.LE.itmax ) 
THEN 
  754               CALL psgetrs( trans, n, 1, af, iaf, jaf, descaf, ipiv,
 
  755     $                       work( ipr ), iw, jw, descw, info )
 
  756               CALL psaxpy( n, one, work( ipr ), iw, jw, descw, 1, x,
 
  757     $                      ix, j+k, descx, 1 )
 
  789            IF( mycol.EQ.icurcol ) 
THEN 
  791                  DO 140 ii = iiw-1, iiw+np-2
 
  792                     IF( work( ipb+ii ).GT.safe2 ) 
THEN 
  793                        work( ipb+ii ) = abs( work( ipr+ii ) ) +
 
  794     $                                   nz*eps*work( ipb+ii )
 
  796                        work( ipb+ii ) = abs( work( ipr+ii ) ) +
 
  797     $                                   nz*eps*work( ipb+ii ) + safe1
 
  805            IF( mycol.EQ.icurcol ) 
THEN 
  806               CALL sgebs2d( ictxt, 
'Rowwise', 
' ', np, 1, work( ipr ),
 
  809               CALL sgebr2d( ictxt, 
'Rowwise', 
' ', np, 1, work( ipr ),
 
  810     $                       descw( lld_ ), myrow, icurcol )
 
  812            descw( csrc_ ) = mycol
 
  813            CALL pslacon( n, work( ipv ), iw, jw, descw, work( ipr ),
 
  814     $                    iw, jw, descw, iwork, est, kase )
 
  815            descw( csrc_ ) = icurcol
 
  822                  CALL psgetrs( transt, n, 1, af, iaf, jaf, descaf,
 
  823     $                          ipiv, work( ipr ), iw, jw, descw, info )
 
  825                  IF( mycol.EQ.icurcol ) 
THEN 
  827                        DO 160 ii = iiw-1, iiw+np-2
 
  828                           work( ipr+ii ) = work( ipb+ii )*
 
  837                  IF( mycol.EQ.icurcol ) 
THEN 
  839                        DO 170 ii = iiw-1, iiw+np-2
 
  840                           work( ipr+ii ) = work( ipb+ii )*
 
  846                  CALL psgetrs( trans, n, 1, af, iaf, jaf, descaf,
 
  847     $                          ipiv, work( ipr ), iw, jw, descw,
 
  856            IF( mycol.EQ.icurcol ) 
THEN 
  858                  DO 180 ii = iixb, iixb+np-1
 
  859                     lstres = 
max( lstres, abs( x( ioffxb+ii ) ) )
 
  862               CALL sgamx2d( ictxt, 
'Column', 
' ', 1, 1, lstres,
 
  863     $                       1, idum, idum, 1, -1, mycol )
 
  865     $            ferr( jjfbe ) = est / lstres
 
  869               ioffxb = ioffxb + ldxb
 
  875         icurcol = mod( icurcol+1, npcol )
 
  879      work( 1 ) = real( lwmin )