169 SUBROUTINE strt03( UPLO, TRANS, DIAG, N, NRHS, A, LDA, SCALE,
170 $ cnorm, tscal, x, ldx, b, ldb, work, resid )
178 CHARACTER diag, trans, uplo
179 INTEGER lda, ldb, ldx, n, nrhs
180 REAL resid, scale, tscal
183 REAL a( lda, * ), b( ldb, * ), cnorm( * ),
184 $ work( * ), x( ldx, * )
191 parameter( one = 1.0e+0, zero = 0.0e+0 )
195 REAL bignum, eps, err, smlnum, tnorm, xnorm, xscal
207 INTRINSIC abs, max, real
213 IF( n.LE.0 .OR. nrhs.LE.0 )
THEN
218 smlnum =
slamch(
'Safe minimum' )
219 bignum = one / smlnum
220 CALL
slabad( smlnum, bignum )
226 IF(
lsame( diag,
'N' ) )
THEN
228 tnorm = max( tnorm, tscal*abs( a( j, j ) )+cnorm( j ) )
232 tnorm = max( tnorm, tscal+cnorm( j ) )
241 CALL
scopy( n, x( 1, j ), 1, work, 1 )
243 xnorm = max( one, abs( x( ix, j ) ) )
244 xscal = ( one / xnorm ) /
REAL( n )
245 CALL
sscal( n, xscal, work, 1 )
246 CALL
strmv( uplo, trans, diag, n, a, lda, work, 1 )
247 CALL
saxpy( n, -scale*xscal, b( 1, j ), 1, work, 1 )
249 err = tscal*abs( work( ix ) )
250 ix =
isamax( n, x( 1, j ), 1 )
251 xnorm = abs( x( ix, j ) )
252 IF( err*smlnum.LE.xnorm )
THEN
259 IF( err*smlnum.LE.tnorm )
THEN
266 resid = max( resid, err )