1 SUBROUTINE psgebal( JOB, N, A, DESCA, ILO, IHI, SCALE, INFO )
15 INTEGER IHI, ILO, INFO, N
19 REAL A( * ), SCALE( * )
172 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
173 $ LLD_, MB_, M_, NB_, N_, RSRC_
174 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
175 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
176 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
178 parameter( zero = 0.0e+0, one = 1.0e+0 )
180 parameter( sclfac = 2.0e+0 )
182 parameter( factor = 0.95e+0 )
186 INTEGER I, ICA, IEXC, IRA, J, K, L, M, LLDA,
187 $ ICTXT, NPROW, NPCOL, MYROW, MYCOL, II, JJ,
189 REAL C, CA, F, G, R, RA, S, SFMAX1, SFMAX2, SFMIN1,
196 LOGICAL SISNAN, LSAME
199 EXTERNAL sisnan, lsame, slamch
202 EXTERNAL psscal, psswap, psamax,
pxerbla,
203 $ blacs_gridinfo,
chk1mat, sgsum2d,
211 ictxt = desca( ctxt_ )
212 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
216 IF( .NOT.lsame( job,
'N' ) .AND. .NOT.lsame( job,
'P' ) .AND.
217 $ .NOT.lsame( job,
'S' ) .AND. .NOT.lsame( job,
'B' ) )
THEN
219 ELSE IF( n.LT.0 )
THEN
222 CALL chk1mat( n, 2, n, 2, 1, 1, desca, 4, info )
225 CALL pxerbla( ictxt,
'PSGEBAL', -info )
239 IF( lsame( job,
'N' ) )
THEN
246 IF( lsame( job,
'S' ) )
260 CALL psswap( l, a, 1, j, desca, 1, a, 1, m, desca, 1 )
261 CALL psswap( n-k+1, a, j, k, desca, desca(m_), a, m, k, desca,
283 CALL pselget(
'All',
'1-Tree', elem, a, j, i, desca )
309 CALL pselget(
'All',
'1-Tree', elem, a, i, j, desca )
324 IF( lsame( job,
'P' ) )
331 sfmin1 = slamch(
'S' ) / slamch(
'P' )
332 sfmax1 = one / sfmin1
333 sfmin2 = sfmin1*sclfac
334 sfmax2 = one / sfmin2
349 CALL infog2l( j, i, desca, nprow, npcol, myrow,
350 $ mycol, ii, jj, arsrc, acsrc )
351 IF( myrow.EQ.arsrc .AND. mycol.EQ.acsrc )
THEN
352 c = c + abs( a( ii + (jj-1)*llda ) )
354 CALL infog2l( i, j, desca, nprow, npcol, myrow,
355 $ mycol, ii, jj, arsrc, acsrc )
356 IF( myrow.EQ.arsrc .AND. mycol.EQ.acsrc )
THEN
357 r = r + abs( a( ii + (jj-1)*llda ) )
362 CALL sgsum2d( ictxt,
'All',
'1-Tree', 2, 1, cr, 2, -1, -1 )
368 CALL psamax( l, ca, ica, a, 1, i, desca, 1 )
369 CALL psamax( n-k+1, ra, ira, a, i, k, desca, desca(m_) )
373 IF( c.EQ.zero .OR. r.EQ.zero )
379 IF( c.GE.g .OR.
max( f, c, ca ).GE.sfmax2 .OR.
380 $
min( r, g, ra ).LE.sfmin2 )
GO TO 170
381 IF( sisnan( c+f+ca+r+g+ra ) )
THEN
386 CALL pxerbla( ictxt,
'PDGEBAL', -info )
400 IF( g.LT.r .OR.
max( r, ra ).GE.sfmax2 .OR.
401 $
min( f, c, g, ca ).LE.sfmin2 )
GO TO 190
413 IF( ( c+r ).GE.factor*s )
415 IF( f.LT.one .AND. scale( i ).LT.one )
THEN
416 IF( f*scale( i ).LE.sfmin1 )
419 IF( f.GT.one .AND. scale( i ).GT.one )
THEN
420 IF( scale( i ).GE.sfmax1 / f )
424 scale( i ) = scale( i )*f
427 CALL psscal( n-k+1, g, a, i, k, desca, desca(m_) )
428 CALL psscal( l, f, a, 1, i, desca, 1 )