01:       SUBROUTINE DLA_LIN_BERR ( N, NZ, NRHS, RES, AYB, BERR )
02: *
03: *     -- LAPACK routine (version 3.2)                                 --
04: *     -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --
05: *     -- Jason Riedy of Univ. of California Berkeley.                 --
06: *     -- November 2008                                                --
07: *
08: *     -- LAPACK is a software package provided by Univ. of Tennessee, --
09: *     -- Univ. of California Berkeley and NAG Ltd.                    --
10: *
11:       IMPLICIT NONE
12: *     ..
13: *     .. Scalar Arguments ..
14:       INTEGER            N, NZ, NRHS
15: *     ..
16: *     .. Array Arguments ..
17:       DOUBLE PRECISION   AYB( N, NRHS ), BERR( NRHS )
18:       DOUBLE PRECISION   RES( N, NRHS )
19: *
20: *     DLA_LIN_BERR computes componentwise relative backward error from
21: *     the formula
22: *         max(i) ( abs(R(i)) / ( abs(op(A_s))*abs(Y) + abs(B_s) )(i) )
23: *     where abs(Z) is the componentwise absolute value of the matrix
24: *     or vector Z.
25: *     ..
26: *     .. Local Scalars ..
27:       DOUBLE PRECISION   TMP
28:       INTEGER            I, J
29: *     ..
30: *     .. Intrinsic Functions ..
31:       INTRINSIC          ABS, MAX
32: *     ..
33: *     .. External Functions ..
34:       EXTERNAL           DLAMCH
35:       DOUBLE PRECISION   DLAMCH
36:       DOUBLE PRECISION   SAFE1
37: *     ..
38: *     .. Executable Statements ..
39: *
40: *     Adding SAFE1 to the numerator guards against spuriously zero
41: *     residuals.  A similar safeguard is in the SLA_yyAMV routine used
42: *     to compute AYB.
43: *
44:       SAFE1 = DLAMCH( 'Safe minimum' )
45:       SAFE1 = (NZ+1)*SAFE1
46: 
47:       DO J = 1, NRHS
48:          BERR(J) = 0.0D+0
49:          DO I = 1, N
50:             IF (AYB(I,J) .NE. 0.0D+0) THEN
51:                TMP = (SAFE1+ABS(RES(I,J)))/AYB(I,J)
52:                BERR(J) = MAX( BERR(J), TMP )
53:             END IF
54: *
55: *     If AYB is exactly 0.0 (and if computed by SLA_yyAMV), then we know
56: *     the true residual also must be exactly 0.0.
57: *
58:          END DO
59:       END DO
60:       END SUBROUTINE
61: