1*> \brief \b DGTT02
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*  Definition:
9*  ===========
10*
11*       SUBROUTINE DGTT02( TRANS, N, NRHS, DL, D, DU, X, LDX, B, LDB,
12*                          RESID )
13*
14*       .. Scalar Arguments ..
15*       CHARACTER          TRANS
16*       INTEGER            LDB, LDX, N, NRHS
17*       DOUBLE PRECISION   RESID
18*       ..
19*       .. Array Arguments ..
20*       DOUBLE PRECISION   B( LDB, * ), D( * ), DL( * ), DU( * ),
21*      $                   X( LDX, * )
22*       ..
23*
24*
25*> \par Purpose:
26*  =============
27*>
28*> \verbatim
29*>
30*> DGTT02 computes the residual for the solution to a tridiagonal
31*> system of equations:
32*>    RESID = norm(B - op(A)*X) / (norm(op(A)) * norm(X) * EPS),
33*> where EPS is the machine epsilon.
34*> The norm used is the 1-norm.
35*> \endverbatim
36*
37*  Arguments:
38*  ==========
39*
40*> \param[in] TRANS
41*> \verbatim
42*>          TRANS is CHARACTER
43*>          Specifies the form of the residual.
44*>          = 'N':  B - A    * X  (No transpose)
45*>          = 'T':  B - A**T * X  (Transpose)
46*>          = 'C':  B - A**H * X  (Conjugate transpose = Transpose)
47*> \endverbatim
48*>
49*> \param[in] N
50*> \verbatim
51*>          N is INTEGTER
52*>          The order of the matrix A.  N >= 0.
53*> \endverbatim
54*>
55*> \param[in] NRHS
56*> \verbatim
57*>          NRHS is INTEGER
58*>          The number of right hand sides, i.e., the number of columns
59*>          of the matrices B and X.  NRHS >= 0.
60*> \endverbatim
61*>
62*> \param[in] DL
63*> \verbatim
64*>          DL is DOUBLE PRECISION array, dimension (N-1)
65*>          The (n-1) sub-diagonal elements of A.
66*> \endverbatim
67*>
68*> \param[in] D
69*> \verbatim
70*>          D is DOUBLE PRECISION array, dimension (N)
71*>          The diagonal elements of A.
72*> \endverbatim
73*>
74*> \param[in] DU
75*> \verbatim
76*>          DU is DOUBLE PRECISION array, dimension (N-1)
77*>          The (n-1) super-diagonal elements of A.
78*> \endverbatim
79*>
80*> \param[in] X
81*> \verbatim
82*>          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
83*>          The computed solution vectors X.
84*> \endverbatim
85*>
86*> \param[in] LDX
87*> \verbatim
88*>          LDX is INTEGER
89*>          The leading dimension of the array X.  LDX >= max(1,N).
90*> \endverbatim
91*>
92*> \param[in,out] B
93*> \verbatim
94*>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
95*>          On entry, the right hand side vectors for the system of
96*>          linear equations.
97*>          On exit, B is overwritten with the difference B - op(A)*X.
98*> \endverbatim
99*>
100*> \param[in] LDB
101*> \verbatim
102*>          LDB is INTEGER
103*>          The leading dimension of the array B.  LDB >= max(1,N).
104*> \endverbatim
105*>
106*> \param[out] RESID
107*> \verbatim
108*>          RESID is DOUBLE PRECISION
109*>          norm(B - op(A)*X) / (norm(op(A)) * norm(X) * EPS)
110*> \endverbatim
111*
112*  Authors:
113*  ========
114*
115*> \author Univ. of Tennessee
116*> \author Univ. of California Berkeley
117*> \author Univ. of Colorado Denver
118*> \author NAG Ltd.
119*
120*> \ingroup double_lin
121*
122*  =====================================================================
123      SUBROUTINE DGTT02( TRANS, N, NRHS, DL, D, DU, X, LDX, B, LDB,
124     $                   RESID )
125*
126*  -- LAPACK test routine --
127*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
128*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129*
130*     .. Scalar Arguments ..
131      CHARACTER          TRANS
132      INTEGER            LDB, LDX, N, NRHS
133      DOUBLE PRECISION   RESID
134*     ..
135*     .. Array Arguments ..
136      DOUBLE PRECISION   B( LDB, * ), D( * ), DL( * ), DU( * ),
137     $                   X( LDX, * )
138*     ..
139*
140*  =====================================================================
141*
142*     .. Parameters ..
143      DOUBLE PRECISION   ONE, ZERO
144      PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
145*     ..
146*     .. Local Scalars ..
147      INTEGER            J
148      DOUBLE PRECISION   ANORM, BNORM, EPS, XNORM
149*     ..
150*     .. External Functions ..
151      LOGICAL            LSAME
152      DOUBLE PRECISION   DASUM, DLAMCH, DLANGT
153      EXTERNAL           LSAME, DASUM, DLAMCH, DLANGT
154*     ..
155*     .. External Subroutines ..
156      EXTERNAL           DLAGTM
157*     ..
158*     .. Intrinsic Functions ..
159      INTRINSIC          MAX
160*     ..
161*     .. Executable Statements ..
162*
163*     Quick exit if N = 0 or NRHS = 0
164*
165      RESID = ZERO
166      IF( N.LE.0 .OR. NRHS.EQ.0 )
167     $   RETURN
168*
169*     Compute the maximum over the number of right hand sides of
170*        norm(B - op(A)*X) / ( norm(op(A)) * norm(X) * EPS ).
171*
172      IF( LSAME( TRANS, 'N' ) ) THEN
173         ANORM = DLANGT( '1', N, DL, D, DU )
174      ELSE
175         ANORM = DLANGT( 'I', N, DL, D, DU )
176      END IF
177*
178*     Exit with RESID = 1/EPS if ANORM = 0.
179*
180      EPS = DLAMCH( 'Epsilon' )
181      IF( ANORM.LE.ZERO ) THEN
182         RESID = ONE / EPS
183         RETURN
184      END IF
185*
186*     Compute B - op(A)*X and store in B.
187*
188      CALL DLAGTM( TRANS, N, NRHS, -ONE, DL, D, DU, X, LDX, ONE, B,
189     $             LDB )
190*
191      DO 10 J = 1, NRHS
192         BNORM = DASUM( N, B( 1, J ), 1 )
193         XNORM = DASUM( N, X( 1, J ), 1 )
194         IF( XNORM.LE.ZERO ) THEN
195            RESID = ONE / EPS
196         ELSE
197            RESID = MAX( RESID, ( ( BNORM / ANORM ) / XNORM ) / EPS )
198         END IF
199   10 CONTINUE
200*
201      RETURN
202*
203*     End of DGTT02
204*
205      END
206