182 SUBROUTINE ctrt05( UPLO, TRANS, DIAG, N, NRHS, A, LDA, B, LDB, X,
183 $ ldx, xact, ldxact, ferr, berr, reslts )
191 CHARACTER diag, trans, uplo
192 INTEGER lda, ldb, ldx, ldxact, n, nrhs
195 REAL berr( * ), ferr( * ), reslts( * )
196 COMPLEX a( lda, * ), b( ldb, * ), x( ldx, * ),
204 parameter( zero = 0.0e+0, one = 1.0e+0 )
207 LOGICAL notran, unit, upper
208 INTEGER i, ifu, imax, j, k
209 REAL axbi, diff, eps, errbnd, ovfl, tmp, unfl, xnorm
219 INTRINSIC abs, aimag, max, min, real
225 cabs1( zdum ) = abs(
REAL( ZDUM ) ) + abs( aimag( zdum ) )
231 IF( n.LE.0 .OR. nrhs.LE.0 )
THEN
238 unfl =
slamch(
'Safe minimum' )
240 upper =
lsame( uplo,
'U' )
241 notran =
lsame( trans,
'N' )
242 unit =
lsame( diag,
'U' )
250 imax =
icamax( n, x( 1, j ), 1 )
251 xnorm = max( cabs1( x( imax, j ) ), unfl )
254 diff = max( diff, cabs1( x( i, j )-xact( i, j ) ) )
257 IF( xnorm.GT.one )
THEN
259 ELSE IF( diff.LE.ovfl*xnorm )
THEN
267 IF( diff / xnorm.LE.ferr( j ) )
THEN
268 errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
283 tmp = cabs1( b( i, k ) )
285 IF( .NOT.notran )
THEN
287 tmp = tmp + cabs1( a( j, i ) )*cabs1( x( j, k ) )
290 $ tmp = tmp + cabs1( x( i, k ) )
293 $ tmp = tmp + cabs1( x( i, k ) )
295 tmp = tmp + cabs1( a( i, j ) )*cabs1( x( j, k ) )
301 tmp = tmp + cabs1( a( i, j ) )*cabs1( x( j, k ) )
304 $ tmp = tmp + cabs1( x( i, k ) )
307 $ tmp = tmp + cabs1( x( i, k ) )
309 tmp = tmp + cabs1( a( j, i ) )*cabs1( x( j, k ) )
316 axbi = min( axbi, tmp )
319 tmp = berr( k ) / ( ( n+1 )*eps+( n+1 )*unfl /
320 $ max( axbi, ( n+1 )*unfl ) )
324 reslts( 2 ) = max( reslts( 2 ), tmp )