LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dtrt05()

subroutine dtrt05 ( character  uplo,
character  trans,
character  diag,
integer  n,
integer  nrhs,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( ldb, * )  b,
integer  ldb,
double precision, dimension( ldx, * )  x,
integer  ldx,
double precision, dimension( ldxact, * )  xact,
integer  ldxact,
double precision, dimension( * )  ferr,
double precision, dimension( * )  berr,
double precision, dimension( * )  reslts 
)

DTRT05

Purpose:
 DTRT05 tests the error bounds from iterative refinement for the
 computed solution to a system of equations A*X = B, where A is a
 triangular n by n matrix.

 RESLTS(1) = test of the error bound
           = norm(X - XACT) / ( norm(X) * FERR )

 A large value is returned if this ratio is not less than one.

 RESLTS(2) = residual from the iterative refinement routine
           = the maximum of BERR / ( (n+1)*EPS + (*) ), where
             (*) = (n+1)*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the matrix A is upper or lower triangular.
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]TRANS
          TRANS is CHARACTER*1
          Specifies the form of the system of equations.
          = 'N':  A * X = B  (No transpose)
          = 'T':  A'* X = B  (Transpose)
          = 'C':  A'* X = B  (Conjugate transpose = Transpose)
[in]DIAG
          DIAG is CHARACTER*1
          Specifies whether or not the matrix A is unit triangular.
          = 'N':  Non-unit triangular
          = 'U':  Unit triangular
[in]N
          N is INTEGER
          The number of rows of the matrices X, B, and XACT, and the
          order of the matrix A.  N >= 0.
[in]NRHS
          NRHS is INTEGER
          The number of columns of the matrices X, B, and XACT.
          NRHS >= 0.
[in]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          The triangular matrix A.  If UPLO = 'U', the leading n by n
          upper triangular part of the array A contains the upper
          triangular matrix, and the strictly lower triangular part of
          A is not referenced.  If UPLO = 'L', the leading n by n lower
          triangular part of the array A contains the lower triangular
          matrix, and the strictly upper triangular part of A is not
          referenced.  If DIAG = 'U', the diagonal elements of A are
          also not referenced and are assumed to be 1.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]B
          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
          The right hand side vectors for the system of linear
          equations.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(1,N).
[in]X
          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
          The computed solution vectors.  Each vector is stored as a
          column of the matrix X.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  LDX >= max(1,N).
[in]XACT
          XACT is DOUBLE PRECISION array, dimension (LDX,NRHS)
          The exact solution vectors.  Each vector is stored as a
          column of the matrix XACT.
[in]LDXACT
          LDXACT is INTEGER
          The leading dimension of the array XACT.  LDXACT >= max(1,N).
[in]FERR
          FERR is DOUBLE PRECISION array, dimension (NRHS)
          The estimated forward error bounds for each solution vector
          X.  If XTRUE is the true solution, FERR bounds the magnitude
          of the largest entry in (X - XTRUE) divided by the magnitude
          of the largest entry in X.
[in]BERR
          BERR is DOUBLE PRECISION array, dimension (NRHS)
          The componentwise relative backward error of each solution
          vector (i.e., the smallest relative change in any entry of A
          or B that makes X an exact solution).
[out]RESLTS
          RESLTS is DOUBLE PRECISION array, dimension (2)
          The maximum over the NRHS solution vectors of the ratios:
          RESLTS(1) = norm(X - XACT) / ( norm(X) * FERR )
          RESLTS(2) = BERR / ( (n+1)*EPS + (*) )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 179 of file dtrt05.f.

181*
182* -- LAPACK test routine --
183* -- LAPACK is a software package provided by Univ. of Tennessee, --
184* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
185*
186* .. Scalar Arguments ..
187 CHARACTER DIAG, TRANS, UPLO
188 INTEGER LDA, LDB, LDX, LDXACT, N, NRHS
189* ..
190* .. Array Arguments ..
191 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), BERR( * ), FERR( * ),
192 $ RESLTS( * ), X( LDX, * ), XACT( LDXACT, * )
193* ..
194*
195* =====================================================================
196*
197* .. Parameters ..
198 DOUBLE PRECISION ZERO, ONE
199 parameter( zero = 0.0d+0, one = 1.0d+0 )
200* ..
201* .. Local Scalars ..
202 LOGICAL NOTRAN, UNIT, UPPER
203 INTEGER I, IFU, IMAX, J, K
204 DOUBLE PRECISION AXBI, DIFF, EPS, ERRBND, OVFL, TMP, UNFL, XNORM
205* ..
206* .. External Functions ..
207 LOGICAL LSAME
208 INTEGER IDAMAX
209 DOUBLE PRECISION DLAMCH
210 EXTERNAL lsame, idamax, dlamch
211* ..
212* .. Intrinsic Functions ..
213 INTRINSIC abs, max, min
214* ..
215* .. Executable Statements ..
216*
217* Quick exit if N = 0 or NRHS = 0.
218*
219 IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
220 reslts( 1 ) = zero
221 reslts( 2 ) = zero
222 RETURN
223 END IF
224*
225 eps = dlamch( 'Epsilon' )
226 unfl = dlamch( 'Safe minimum' )
227 ovfl = one / unfl
228 upper = lsame( uplo, 'U' )
229 notran = lsame( trans, 'N' )
230 unit = lsame( diag, 'U' )
231*
232* Test 1: Compute the maximum of
233* norm(X - XACT) / ( norm(X) * FERR )
234* over all the vectors X and XACT using the infinity-norm.
235*
236 errbnd = zero
237 DO 30 j = 1, nrhs
238 imax = idamax( n, x( 1, j ), 1 )
239 xnorm = max( abs( x( imax, j ) ), unfl )
240 diff = zero
241 DO 10 i = 1, n
242 diff = max( diff, abs( x( i, j )-xact( i, j ) ) )
243 10 CONTINUE
244*
245 IF( xnorm.GT.one ) THEN
246 GO TO 20
247 ELSE IF( diff.LE.ovfl*xnorm ) THEN
248 GO TO 20
249 ELSE
250 errbnd = one / eps
251 GO TO 30
252 END IF
253*
254 20 CONTINUE
255 IF( diff / xnorm.LE.ferr( j ) ) THEN
256 errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
257 ELSE
258 errbnd = one / eps
259 END IF
260 30 CONTINUE
261 reslts( 1 ) = errbnd
262*
263* Test 2: Compute the maximum of BERR / ( (n+1)*EPS + (*) ), where
264* (*) = (n+1)*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
265*
266 ifu = 0
267 IF( unit )
268 $ ifu = 1
269 DO 90 k = 1, nrhs
270 DO 80 i = 1, n
271 tmp = abs( b( i, k ) )
272 IF( upper ) THEN
273 IF( .NOT.notran ) THEN
274 DO 40 j = 1, i - ifu
275 tmp = tmp + abs( a( j, i ) )*abs( x( j, k ) )
276 40 CONTINUE
277 IF( unit )
278 $ tmp = tmp + abs( x( i, k ) )
279 ELSE
280 IF( unit )
281 $ tmp = tmp + abs( x( i, k ) )
282 DO 50 j = i + ifu, n
283 tmp = tmp + abs( a( i, j ) )*abs( x( j, k ) )
284 50 CONTINUE
285 END IF
286 ELSE
287 IF( notran ) THEN
288 DO 60 j = 1, i - ifu
289 tmp = tmp + abs( a( i, j ) )*abs( x( j, k ) )
290 60 CONTINUE
291 IF( unit )
292 $ tmp = tmp + abs( x( i, k ) )
293 ELSE
294 IF( unit )
295 $ tmp = tmp + abs( x( i, k ) )
296 DO 70 j = i + ifu, n
297 tmp = tmp + abs( a( j, i ) )*abs( x( j, k ) )
298 70 CONTINUE
299 END IF
300 END IF
301 IF( i.EQ.1 ) THEN
302 axbi = tmp
303 ELSE
304 axbi = min( axbi, tmp )
305 END IF
306 80 CONTINUE
307 tmp = berr( k ) / ( ( n+1 )*eps+( n+1 )*unfl /
308 $ max( axbi, ( n+1 )*unfl ) )
309 IF( k.EQ.1 ) THEN
310 reslts( 2 ) = tmp
311 ELSE
312 reslts( 2 ) = max( reslts( 2 ), tmp )
313 END IF
314 90 CONTINUE
315*
316 RETURN
317*
318* End of DTRT05
319*
integer function idamax(n, dx, incx)
IDAMAX
Definition idamax.f:71
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the caller graph for this function: