206 SUBROUTINE sgtrfs( TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2,
207 $ IPIV, B, LDB, X, LDX, FERR, BERR, WORK, IWORK,
216 INTEGER INFO, LDB, LDX, N, NRHS
219 INTEGER IPIV( * ), IWORK( * )
220 REAL B( LDB, * ), BERR( * ), D( * ), DF( * ),
221 $ dl( * ), dlf( * ), du( * ), du2( * ), duf( * ),
222 $ ferr( * ), work( * ), x( ldx, * )
229 PARAMETER ( ITMAX = 5 )
231 parameter( zero = 0.0e+0, one = 1.0e+0 )
233 parameter( two = 2.0e+0 )
235 parameter( three = 3.0e+0 )
239 CHARACTER TRANSN, TRANST
240 INTEGER COUNT, I, J, KASE, NZ
241 REAL EPS, LSTRES, S, SAFE1, SAFE2, SAFMIN
255 EXTERNAL lsame, slamch
262 notran = lsame( trans,
'N' )
263 IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
264 $ lsame( trans,
'C' ) )
THEN
266 ELSE IF( n.LT.0 )
THEN
268 ELSE IF( nrhs.LT.0 )
THEN
270 ELSE IF( ldb.LT.max( 1, n ) )
THEN
272 ELSE IF( ldx.LT.max( 1, n ) )
THEN
276 CALL xerbla(
'SGTRFS', -info )
282 IF( n.EQ.0 .OR. nrhs.EQ.0 )
THEN
301 eps = slamch(
'Epsilon' )
302 safmin = slamch(
'Safe minimum' )
319 CALL scopy( n, b( 1, j ), 1, work( n+1 ), 1 )
320 CALL slagtm( trans, n, 1, -one, dl, d, du, x( 1, j ), ldx, one,
328 work( 1 ) = abs( b( 1, j ) ) + abs( d( 1 )*x( 1, j ) )
330 work( 1 ) = abs( b( 1, j ) ) + abs( d( 1 )*x( 1, j ) ) +
331 $ abs( du( 1 )*x( 2, j ) )
333 work( i ) = abs( b( i, j ) ) +
334 $ abs( dl( i-1 )*x( i-1, j ) ) +
335 $ abs( d( i )*x( i, j ) ) +
336 $ abs( du( i )*x( i+1, j ) )
338 work( n ) = abs( b( n, j ) ) +
339 $ abs( dl( n-1 )*x( n-1, j ) ) +
340 $ abs( d( n )*x( n, j ) )
344 work( 1 ) = abs( b( 1, j ) ) + abs( d( 1 )*x( 1, j ) )
346 work( 1 ) = abs( b( 1, j ) ) + abs( d( 1 )*x( 1, j ) ) +
347 $ abs( dl( 1 )*x( 2, j ) )
349 work( i ) = abs( b( i, j ) ) +
350 $ abs( du( i-1 )*x( i-1, j ) ) +
351 $ abs( d( i )*x( i, j ) ) +
352 $ abs( dl( i )*x( i+1, j ) )
354 work( n ) = abs( b( n, j ) ) +
355 $ abs( du( n-1 )*x( n-1, j ) ) +
356 $ abs( d( n )*x( n, j ) )
371 IF( work( i ).GT.safe2 )
THEN
372 s = max( s, abs( work( n+i ) ) / work( i ) )
374 s = max( s, ( abs( work( n+i ) )+safe1 ) /
375 $ ( work( i )+safe1 ) )
386 IF( berr( j ).GT.eps .AND. two*berr( j ).LE.lstres .AND.
387 $ count.LE.itmax )
THEN
391 CALL sgttrs( trans, n, 1, dlf, df, duf, du2, ipiv,
392 $ work( n+1 ), n, info )
393 CALL saxpy( n, one, work( n+1 ), 1, x( 1, j ), 1 )
422 IF( work( i ).GT.safe2 )
THEN
423 work( i ) = abs( work( n+i ) ) + nz*eps*work( i )
425 work( i ) = abs( work( n+i ) ) + nz*eps*work( i ) + safe1
431 CALL slacn2( n, work( 2*n+1 ), work( n+1 ), iwork, ferr( j ),
438 CALL sgttrs( transt, n, 1, dlf, df, duf, du2, ipiv,
439 $ work( n+1 ), n, info )
441 work( n+i ) = work( i )*work( n+i )
448 work( n+i ) = work( i )*work( n+i )
450 CALL sgttrs( transn, n, 1, dlf, df, duf, du2, ipiv,
451 $ work( n+1 ), n, info )
460 lstres = max( lstres, abs( x( i, j ) ) )
463 $ ferr( j ) = ferr( j ) / lstres
subroutine xerbla(srname, info)
subroutine saxpy(n, sa, sx, incx, sy, incy)
SAXPY
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine sgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SGTRFS
subroutine sgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, info)
SGTTRS
subroutine slacn2(n, v, x, isgn, est, kase, isave)
SLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine slagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)
SLAGTM performs a matrix-matrix product of the form C = αAB+βC, where A is a tridiagonal matrix,...