207 SUBROUTINE cgtrfs( TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2,
208 $ IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK,
217 INTEGER INFO, LDB, LDX, N, NRHS
221 REAL ( * ), FERR( * ), RWORK( * )
222 COMPLEX B( , * ), D( * ), DF( * ), DL( * ),
223 $ dlf( * ), du( * ), du2( * ), duf( * ),
224 $ work( * ), x( ldx, * )
231 PARAMETER ( ITMAX = 5 )
233 parameter( zero = 0.0e+0, one = 1.0e+0 )
235 parameter( two = 2.0e+0 )
237 PARAMETER ( three = 3.0e+0 )
241 CHARACTER TRANSN, TRANST
242 INTEGER COUNT, I, J, KASE, NZ
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' )
328 CALL ccopy( n, b( 1, j ), 1, work, 1 )
329 CALL clagtm( trans, n, 1, -one, dl, d, du, x( 1, j ), ldx, one,
337 rwork( 1 ) = cabs1( b( 1, j ) ) +
338 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) )
340 rwork( 1 ) = cabs1( b( 1, j ) ) +
341 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) ) +
342 $ cabs1( du( 1 ) )*cabs1( x( 2, j ) )
344 rwork( i ) = cabs1( b( i, j ) ) +
345 $ cabs1( dl( i-1 ) )*cabs1( x( i-1, j ) ) +
346 $ cabs1( d( i ) )*cabs1( x( i, j ) ) +
347 $ cabs1( du( i ) )*cabs1( x( i+1, j ) )
349 rwork( n ) = cabs1( b( n, j ) ) +
350 $ cabs1( dl( n-1 ) )*cabs1( x( n-1, j ) ) +
351 $ cabs1( d( n ) )*cabs1( x( n, j ) )
355 rwork( 1 ) = cabs1( b( 1, j ) ) +
356 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) )
358 rwork( 1 ) = cabs1( b( 1, j ) ) +
359 $ cabs1( d( 1 ) )*cabs1( x( 1, j ) ) +
360 $ cabs1( dl( 1 ) )*cabs1( x( 2, j ) )
362 rwork( i ) = cabs1( b( i, j ) ) +
363 $ cabs1( du( i-1 ) )*cabs1( x( i-1, j ) ) +
364 $ cabs1( d( i ) )*cabs1( x( i, j ) ) +
365 $ cabs1( dl( i ) )*cabs1( x( i+1, j ) )
367 rwork( n ) = cabs1( b( n, j ) ) +
368 $ cabs1( du( n-1 ) )*cabs1( x( n-1, j ) ) +
369 $ cabs1( d( n ) )*cabs1( x( n, j ) )
384 IF( rwork( i ).GT.safe2 )
THEN
385 s =
max( s, cabs1( work( i ) ) / rwork( i ) )
387 s =
max( s, ( cabs1( work( i ) )+safe1 ) /
388 $ ( rwork( i )+safe1 ) )
399 IF( berr( j ).GT.eps .AND. two*berr( j ).LE.lstres .AND.
400 $ count.LE.itmax )
THEN
404 CALL cgttrs( trans, n, 1, dlf, df, duf, du2, ipiv, work, n,
406 CALL caxpy( n,
cmplx( one ), work, 1, x( 1, j ), 1 )
435 IF( rwork( i ).GT.safe2 )
THEN
436 rwork( i ) = cabs1( work( i ) ) + nz*eps*rwork( i )
438 rwork( i ) = cabs1( work( i ) ) + nz*eps*rwork( i ) +
445 CALL clacn2( n, work( n+1 ), work, ferr( j ), kase, isave )
451 CALL cgttrs( transt, n, 1, dlf, df, duf, du2, ipiv, work,
454 work( i ) = rwork( i )*work( i )
461 work( i ) = rwork( i )*work( i )
463 CALL cgttrs( transn, n, 1, dlf, df, duf, du2, ipiv, work,
473 lstres =
max( lstres, cabs1( x( i, j ) )
476 $ ferr( j ) = ferr( j ) / lstres
subroutine cgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CGTRFS