205 SUBROUTINE cgtrfs( TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF,
207 $ IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK,
216 INTEGER INFO, LDB, LDX, N, NRHS
220 REAL BERR( * ), FERR( * ), RWORK( * )
221 COMPLEX B( LDB, * ), D( * ), DF( * ), DL( * ),
222 $ dlf( * ), du( * ), du2( * ), duf( * ),
223 $ work( * ), x( ldx, * )
230 PARAMETER ( ITMAX = 5 )
232 parameter( zero = 0.0e+0, one = 1.0e+0 )
234 parameter( two = 2.0e+0 )
236 parameter( three = 3.0e+0 )
240 CHARACTER TRANSN, TRANST
241 INTEGER COUNT, I, J, KASE, NZ
242 REAL EPS, LSTRES, S, SAFE1, SAFE2, SAFMIN
253 INTRINSIC abs, aimag, cmplx, max, real
258 EXTERNAL LSAME, SLAMCH
264 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
271 notran = lsame( trans,
'N' )
272 IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
273 $ lsame( trans,
'C' ) )
THEN
275 ELSE IF( n.LT.0 )
THEN
277 ELSE IF( nrhs.LT.0 )
THEN
279 ELSE IF( ldb.LT.max( 1, n ) )
THEN
281 ELSE IF( ldx.LT.max( 1, n ) )
THEN
285 CALL xerbla(
'CGTRFS', -info )
291 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
310 eps = slamch(
'Epsilon' )
311 safmin = slamch(
'Safe minimum' )
312 safe1 = real( nz )*safmin
328 CALL ccopy( n, b( 1, j ), 1, work, 1 )
329 CALL clagtm( trans, n, 1, -one, dl, d, du, x( 1, j ), ldx,
338 rwork( 1 ) = cabs1( b( 1, j ) ) +
339 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) )
341 rwork( 1 ) = cabs1( b( 1, j ) ) +
342 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) ) +
343 $ cabs1( du( 1 ) )*cabs1( x( 2, j ) )
345 rwork( i ) = cabs1( b( i, j ) ) +
346 $ cabs1( dl( i-1 ) )*cabs1( x( i-1, j ) ) +
347 $ cabs1( d( i ) )*cabs1( x( i, j ) ) +
348 $ cabs1( du( i ) )*cabs1( x( i+1, j ) )
350 rwork( n ) = cabs1( b( n, j ) ) +
351 $ cabs1( dl( n-1 ) )*cabs1( x( n-1, j ) ) +
352 $ cabs1( d( n ) )*cabs1( x( n, j ) )
356 rwork( 1 ) = cabs1( b( 1, j ) ) +
357 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) )
359 rwork( 1 ) = cabs1( b( 1, j ) ) +
360 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) ) +
361 $ cabs1( dl( 1 ) )*cabs1( x( 2, j ) )
363 rwork( i ) = cabs1( b( i, j ) ) +
364 $ cabs1( du( i-1 ) )*cabs1( x( i-1, j ) ) +
365 $ cabs1( d( i ) )*cabs1( x( i, j ) ) +
366 $ cabs1( dl( i ) )*cabs1( x( i+1, j ) )
368 rwork( n ) = cabs1( b( n, j ) ) +
369 $ cabs1( du( n-1 ) )*cabs1( x( n-1, j ) ) +
370 $ cabs1( d( n ) )*cabs1( x( n, j ) )
385 IF( rwork( i ).GT.safe2 )
THEN
386 s = max( s, cabs1( work( i ) ) / rwork( i ) )
388 s = max( s, ( cabs1( work( i ) )+safe1 ) /
389 $ ( rwork( i )+safe1 ) )
400 IF( berr( j ).GT.eps .AND. two*berr( j ).LE.lstres .AND.
401 $ count.LE.itmax )
THEN
405 CALL cgttrs( trans, n, 1, dlf, df, duf, du2, ipiv, work,
408 CALL caxpy( n, cmplx( one ), work, 1, x( 1, j ), 1 )
437 IF( rwork( i ).GT.safe2 )
THEN
438 rwork( i ) = cabs1( work( i ) ) + real( nz )*
441 rwork( i ) = cabs1( work( i ) ) + real( nz )*
442 $ eps*rwork( i ) + safe1
448 CALL clacn2( n, work( n+1 ), work, ferr( j ), kase, isave )
454 CALL cgttrs( transt, n, 1, dlf, df, duf, du2, ipiv,
458 work( i ) = rwork( i )*work( i )
465 work( i ) = rwork( i )*work( i )
467 CALL cgttrs( transn, n, 1, dlf, df, duf, du2, ipiv,
478 lstres = max( lstres, cabs1( x( i, j ) ) )
481 $ ferr( j ) = ferr( j ) / lstres