150 SUBROUTINE cptt05( N, NRHS, D, E, B, LDB, X, LDX, XACT, LDXACT,
151 $ ferr, berr, reslts )
159 INTEGER ldb, ldx, ldxact, n, nrhs
162 REAL berr( * ), d( * ), ferr( * ), reslts( * )
163 COMPLEX b( ldb, * ), e( * ), x( ldx, * ),
171 parameter( zero = 0.0e+0, one = 1.0e+0 )
174 INTEGER i, imax, j, k, nz
175 REAL axbi, diff, eps, errbnd, ovfl, tmp, unfl, xnorm
184 INTRINSIC abs, aimag, max, min, real
190 cabs1( zdum ) = abs(
REAL( ZDUM ) ) + abs( aimag( zdum ) )
196 IF( n.LE.0 .OR. nrhs.LE.0 )
THEN
203 unfl =
slamch(
'Safe minimum' )
213 imax =
icamax( n, x( 1, j ), 1 )
214 xnorm = max( cabs1( x( imax, j ) ), unfl )
217 diff = max( diff, cabs1( x( i, j )-xact( i, j ) ) )
220 IF( xnorm.GT.one )
THEN
222 ELSE IF( diff.LE.ovfl*xnorm )
THEN
230 IF( diff / xnorm.LE.ferr( j ) )
THEN
231 errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
243 axbi = cabs1( b( 1, k ) ) + cabs1( d( 1 )*x( 1, k ) )
245 axbi = cabs1( b( 1, k ) ) + cabs1( d( 1 )*x( 1, k ) ) +
246 $ cabs1( e( 1 ) )*cabs1( x( 2, k ) )
248 tmp = cabs1( b( i, k ) ) + cabs1( e( i-1 ) )*
249 $ cabs1( x( i-1, k ) ) + cabs1( d( i )*x( i, k ) ) +
250 $ cabs1( e( i ) )*cabs1( x( i+1, k ) )
251 axbi = min( axbi, tmp )
253 tmp = cabs1( b( n, k ) ) + cabs1( e( n-1 ) )*
254 $ cabs1( x( n-1, k ) ) + cabs1( d( n )*x( n, k ) )
255 axbi = min( axbi, tmp )
257 tmp = berr( k ) / ( nz*eps+nz*unfl / max( axbi, nz*unfl ) )
261 reslts( 2 ) = max( reslts( 2 ), tmp )