171 SUBROUTINE ctrt03( UPLO, TRANS, DIAG, N, NRHS, A, LDA, SCALE,
172 $ cnorm, tscal, x, ldx, b, ldb, work, resid )
180 CHARACTER diag, trans, uplo
181 INTEGER lda, ldb, ldx, n, nrhs
182 REAL resid, scale, tscal
186 COMPLEX a( lda, * ), b( ldb, * ), work( * ),
194 parameter( one = 1.0e+0, zero = 0.0e+0 )
198 REAL eps, err, smlnum, tnorm, xnorm, xscal
210 INTRINSIC abs, cmplx, max, real
216 IF( n.LE.0 .OR. nrhs.LE.0 )
THEN
221 smlnum =
slamch(
'Safe minimum' )
227 IF(
lsame( diag,
'N' ) )
THEN
229 tnorm = max( tnorm, tscal*abs( a( j, j ) )+cnorm( j ) )
233 tnorm = max( tnorm, tscal+cnorm( j ) )
242 CALL
ccopy( n, x( 1, j ), 1, work, 1 )
244 xnorm = max( one, abs( x( ix, j ) ) )
245 xscal = ( one / xnorm ) /
REAL( n )
246 CALL
csscal( n, xscal, work, 1 )
247 CALL
ctrmv( uplo, trans, diag, n, a, lda, work, 1 )
248 CALL
caxpy( n, cmplx( -scale*xscal ), b( 1, j ), 1, work, 1 )
250 err = tscal*abs( work( ix ) )
251 ix =
icamax( n, x( 1, j ), 1 )
252 xnorm = abs( x( ix, j ) )
253 IF( err*smlnum.LE.xnorm )
THEN
260 IF( err*smlnum.LE.tnorm )
THEN
267 resid = max( resid, err )