1 SUBROUTINE pstrrfs( UPLO, TRANS, DIAG, N, NRHS, A, IA, JA, DESCA,
2 $ B, IB, JB, DESCB, X, IX, JX, DESCX, FERR,
3 $ BERR, WORK, LWORK, IWORK, LIWORK, INFO )
11 CHARACTER DIAG, TRANS, UPLO
12 INTEGER INFO, IA, IB, IX, JA, JB, JX, LIWORK, LWORK,
16 INTEGER DESCA( * ), DESCB( * ), DESCX( * ), IWORK( * )
17 REAL A( * ), B( * ), BERR( * ), FERR( * ),
247 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
248 $ LLD_, MB_, M_, NB_, N_, RSRC_
249 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
250 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
251 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
253 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
256 LOGICAL LQUERY, NOTRAN, NOUNIT, UPPER
258 INTEGER IAROW, IXBCOL, IXBROW, IXCOL, IXROW, ICOFFA,
259 $ icoffb, icoffx, ictxt, icurcol, idum, ii, iixb,
260 $ iiw, ioffxb, ipb, ipr, ipv, iroffa, iroffb,
261 $ iroffx, iw, j, jbrhs, jj, jjfbe, jjxb, jn, jw,
262 $ k, kase, ldxb, liwmin, lwmin, mycol, myrhs,
263 $ myrow, np, np0, npcol, npmod, nprow, nz
264 REAL EPS, EST, LSTRES, S, SAFE1, SAFE2, SAFMIN
267 INTEGER DESCW( DLEN_ ), IDUM1( 5 ), IDUM2( 5 )
271 INTEGER ICEIL, INDXG2P, NUMROC
273 EXTERNAL iceil, indxg2p, lsame, numroc, pslamch
278 $ pscopy,
pslacon, pstrsv, pstrmv,
279 $
pxerbla, sgamx2d, sgebr2d, sgebs2d
282 INTRINSIC abs, ichar,
max,
min, mod, real
288 ictxt = desca( ctxt_ )
289 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
294 IF( nprow.EQ.-1 )
THEN
295 info = -( 900+ctxt_ )
297 CALL chk1mat( n, 4, n, 4, ia, ja, desca, 9, info )
298 CALL chk1mat( n, 4, nrhs, 5, ib, jb, descb, 13, info )
299 CALL chk1mat( n, 4, nrhs, 5, ix, jx, descx, 17, info )
301 upper = lsame( uplo,
'U' )
302 notran = lsame( trans,
'N' )
303 nounit = lsame( diag,
'N' )
304 iroffa = mod( ia-1, desca( mb_ ) )
305 icoffa = mod( ja-1, desca( nb_ ) )
306 iroffb = mod( ib-1, descb( mb_ ) )
307 icoffb = mod( jb-1, descb( nb_ ) )
308 iroffx = mod( ix-1, descx( mb_ ) )
309 icoffx = mod( jx-1, descx( nb_ ) )
310 iarow = indxg2p( ia, desca( mb_ ), myrow, desca( rsrc_ ),
312 CALL infog2l( ib, jb, descb, nprow, npcol, myrow, mycol,
313 $ iixb, jjxb, ixbrow, ixbcol )
314 ixrow = indxg2p( ix, descx( mb_ ), myrow, descx( rsrc_ ),
316 ixcol = indxg2p( jx, descx( nb_ ), mycol, descx( csrc_ ),
318 npmod = numroc( n+iroffa, desca( mb_ ), myrow, iarow,
321 work( 1 ) = real( lwmin )
324 lquery = ( lwork.EQ.-1 .OR. liwork.EQ.-1 )
326 IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
328 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND.
329 $ .NOT.lsame( trans,
'C' ) )
THEN
331 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag,
'U' ) )
THEN
333 ELSE IF( n.LT.0 )
THEN
335 ELSE IF( nrhs.LT.0 )
THEN
337 ELSE IF( iroffa.NE.0 )
THEN
339 ELSE IF( icoffa.NE.0 )
THEN
341 ELSE IF( desca( mb_ ).NE.desca( nb_ ) )
THEN
343 ELSE IF( iroffa.NE.iroffb .OR. iarow.NE.ixbrow )
THEN
345 ELSE IF( desca( mb_ ).NE.descb( mb_ ) )
THEN
347 ELSE IF( ictxt.NE.descb( ctxt_ ) )
THEN
348 info = -( 1300+ctxt_ )
349 ELSE IF( iroffx.NE.0 .OR. ixbrow.NE.ixrow )
THEN
351 ELSE IF( icoffb.NE.icoffx .OR. ixbcol.NE.ixcol )
THEN
353 ELSE IF( descb( mb_ ).NE.descx( mb_ ) )
THEN
355 ELSE IF( descb( nb_ ).NE.descx( nb_ ) )
THEN
357 ELSE IF( ictxt.NE.descx( ctxt_ ) )
THEN
358 info = -( 1700+ctxt_ )
359 ELSE IF( lwork.LT.lwmin .AND. .NOT.lquery )
THEN
361 ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery )
THEN
367 idum1( 1 ) = ichar(
'U' )
369 idum1( 1 ) = ichar(
'L' )
373 idum1( 2 ) = ichar(
'N' )
374 ELSE IF( lsame( trans,
'T' ) )
THEN
375 idum1( 2 ) = ichar(
'T' )
377 idum1( 2 ) = ichar(
'C' )
381 idum1( 3 ) = ichar(
'N' )
383 idum1( 3 ) = ichar(
'U' )
386 IF( lwork.EQ.-1 )
THEN
392 IF( liwork.EQ.-1 )
THEN
398 CALL pchk1mat( n, 4, n, 4, ia, ja, desca, 9, 0, idum1, idum2,
400 CALL pchk2mat( n, 4, nrhs, 5, ib, jb, descb, 13, n, 4, nrhs, 5,
401 $ ix, jx, descx, 17, 5, idum1, idum2, info )
404 CALL pxerbla( ictxt,
'PSTRRFS', -info )
406 ELSE IF( lquery )
THEN
411 myrhs = numroc( jb+nrhs-1, descb( nb_ ), mycol, descb( csrc_ ),
416 IF( n.LE.1 .OR. nrhs.EQ.0 )
THEN
417 DO 10 jj = jjfbe, myrhs
430 np0 = numroc( n+iroffb, descb( mb_ ), myrow, ixbrow, nprow )
431 CALL descset( descw, n+iroffb, 1, desca( mb_ ), 1, ixbrow, ixbcol,
432 $ ictxt,
max( 1, np0 ) )
436 IF( myrow.EQ.ixbrow )
THEN
446 ioffxb = ( jjxb-1 )*ldxb
451 eps = pslamch( ictxt,
'Epsilon' )
452 safmin = pslamch( ictxt,
'Safe minimum' )
455 jn =
min( iceil( jb, descb( nb_ ) )*descb( nb_ ), jb+nrhs-1 )
460 DO 90 k = 0, jbrhs - 1
465 CALL pscopy( n, x, ix, jx+k, descx, 1, work( ipr ), iw, jw,
467 CALL pstrmv( uplo, trans, diag, n, a, ia, ja, desca,
468 $ work( ipr ), iw, jw, descw, 1 )
469 CALL psaxpy( n, -one, b, ib, jb+k, descb, 1, work( ipr ), iw,
481 IF( mycol.EQ.ixbcol )
THEN
483 DO 20 ii = iixb, iixb + np - 1
484 work( iiw+ii-iixb ) = abs( b( ii+ioffxb ) )
489 CALL psatrmv( uplo, trans, diag, n, one, a, ia, ja, desca, x,
490 $ ix, jx+k, descx, 1, one, work( ipb ), iw, jw,
494 IF( mycol.EQ.ixbcol )
THEN
496 DO 30 ii = iiw - 1, iiw + np - 2
497 IF( work( ipb+ii ).GT.safe2 )
THEN
498 s =
max( s, abs( work( ipr+ii ) ) /
501 s =
max( s, ( abs( work( ipr+ii ) )+safe1 ) /
502 $ ( work( ipb+ii )+safe1 ) )
508 CALL sgamx2d( ictxt,
'All',
' ', 1, 1, s, 1, idum, idum, 1,
510 IF( mycol.EQ.ixbcol )
535 IF( mycol.EQ.ixbcol )
THEN
537 DO 40 ii = iiw - 1, iiw + np - 2
538 IF( work( ipb+ii ).GT.safe2 )
THEN
539 work( ipb+ii ) = abs( work( ipr+ii ) ) +
540 $ nz*eps*work( ipb+ii )
542 work( ipb+ii ) = abs( work( ipr+ii ) ) +
543 $ nz*eps*work( ipb+ii ) + safe1
551 IF( mycol.EQ.ixbcol )
THEN
552 CALL sgebs2d( ictxt,
'Rowwise',
' ', np, 1, work( ipr ),
555 CALL sgebr2d( ictxt,
'Rowwise',
' ', np, 1, work( ipr ),
556 $ descw( lld_ ), myrow, ixbcol )
558 descw( csrc_ ) = mycol
559 CALL pslacon( n, work( ipv ), iw, jw, descw, work( ipr ),
560 $ iw, jw, descw, iwork, est, kase )
561 descw( csrc_ ) = ixbcol
568 CALL pstrsv( uplo, transt, diag, n, a, ia, ja, desca,
569 $ work( ipr ), iw, jw, descw, 1 )
570 IF( mycol.EQ.ixbcol )
THEN
572 DO 60 ii = iiw - 1, iiw + np - 2
573 work( ipr+ii ) = work( ipb+ii )*work( ipr+ii )
581 IF( mycol.EQ.ixbcol )
THEN
583 DO 70 ii = iiw - 1, iiw + np - 2
584 work( ipr+ii ) = work( ipb+ii )*work( ipr+ii )
588 CALL pstrsv( uplo, trans, diag, n, a, ia, ja, desca,
589 $ work( ipr ), iw, jw, descw, 1 )
597 IF( mycol.EQ.ixbcol )
THEN
599 DO 80 ii = iixb, iixb + np - 1
600 lstres =
max( lstres, abs( x( ioffxb+ii ) ) )
603 CALL sgamx2d( ictxt,
'Column',
' ', 1, 1, lstres, 1, idum,
604 $ idum, 1, -1, mycol )
606 $ ferr( jjfbe ) = est / lstres
610 ioffxb = ioffxb + ldxb
616 icurcol = mod( ixbcol+1, npcol )
620 DO 180 j = jn + 1, jb + nrhs - 1, descb( nb_ )
621 jbrhs =
min( jb+nrhs-j, descb( nb_ ) )
622 descw( csrc_ ) = icurcol
624 DO 170 k = 0, jbrhs - 1
629 CALL pscopy( n, x, ix, j+k, descx, 1, work( ipr ), iw, jw,
631 CALL pstrmv( uplo, trans, diag, n, a, ia, ja, desca,
632 $ work( ipr ), iw, jw, descw, 1 )
633 CALL psaxpy( n, -one, b, ib, j+k, descb, 1, work( ipr ),
646 IF( mycol.EQ.ixbcol )
THEN
648 DO 100 ii = iixb, iixb + np - 1
649 work( iiw+ii-iixb ) = abs( b( ii+ioffxb ) )
654 CALL psatrmv( uplo, trans, diag, n, one, a, ia, ja, desca,
655 $ x, ix, j+k, descx, 1, one, work( ipb ), iw,
659 IF( mycol.EQ.ixbcol )
THEN
661 DO 110 ii = iiw - 1, iiw + np - 2
662 IF( work( ipb+ii ).GT.safe2 )
THEN
663 s =
max( s, abs( work( ipr+ii ) ) /
666 s =
max( s, ( abs( work( ipr+ii ) )+safe1 ) /
667 $ ( work( ipb+ii )+safe1 ) )
673 CALL sgamx2d( ictxt,
'All',
' ', 1, 1, s, 1, idum, idum, 1,
675 IF( mycol.EQ.ixbcol )
702 IF( mycol.EQ.ixbcol )
THEN
704 DO 120 ii = iiw - 1, iiw + np - 2
705 IF( work( ipb+ii ).GT.safe2 )
THEN
706 work( ipb+ii ) = abs( work( ipr+ii ) ) +
707 $ nz*eps*work( ipb+ii )
709 work( ipb+ii ) = abs( work( ipr+ii ) ) +
710 $ nz*eps*work( ipb+ii ) + safe1
718 IF( mycol.EQ.ixbcol )
THEN
719 CALL sgebs2d( ictxt,
'Rowwise',
' ', np, 1, work( ipr ),
722 CALL sgebr2d( ictxt,
'Rowwise',
' ', np, 1, work( ipr ),
723 $ descw( lld_ ), myrow, ixbcol )
725 descw( csrc_ ) = mycol
726 CALL pslacon( n, work( ipv ), iw, jw, descw, work( ipr ),
727 $ iw, jw, descw, iwork, est, kase )
728 descw( csrc_ ) = ixbcol
735 CALL pstrsv( uplo, transt, diag, n, a, ia, ja, desca,
736 $ work( ipr ), iw, jw, descw, 1 )
737 IF( mycol.EQ.ixbcol )
THEN
739 DO 140 ii = iiw - 1, iiw + np - 2
740 work( ipr+ii ) = work( ipb+ii )*
749 IF( mycol.EQ.ixbcol )
THEN
751 DO 150 ii = iiw - 1, iiw + np - 2
752 work( ipr+ii ) = work( ipb+ii )*
757 CALL pstrsv( uplo, trans, diag, n, a, ia, ja, desca,
758 $ work( ipr ), iw, jw, descw, 1 )
766 IF( mycol.EQ.ixbcol )
THEN
768 DO 160 ii = iixb, iixb + np - 1
769 lstres =
max( lstres, abs( x( ioffxb+ii ) ) )
772 CALL sgamx2d( ictxt,
'Column',
' ', 1, 1, lstres, 1,
773 $ idum, idum, 1, -1, mycol )
775 $ ferr( jjfbe ) = est / lstres
779 ioffxb = ioffxb + ldxb
785 icurcol = mod( icurcol+1, npcol )
789 work( 1 ) = real( lwmin )