1*> \brief \b SPTT02
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 SPTT02( N, NRHS, D, E, X, LDX, B, LDB, RESID )
12*
13*       .. Scalar Arguments ..
14*       INTEGER            LDB, LDX, N, NRHS
15*       REAL               RESID
16*       ..
17*       .. Array Arguments ..
18*       REAL               B( LDB, * ), D( * ), E( * ), X( LDX, * )
19*       ..
20*
21*
22*> \par Purpose:
23*  =============
24*>
25*> \verbatim
26*>
27*> SPTT02 computes the residual for the solution to a symmetric
28*> tridiagonal system of equations:
29*>    RESID = norm(B - A*X) / (norm(A) * norm(X) * EPS),
30*> where EPS is the machine epsilon.
31*> \endverbatim
32*
33*  Arguments:
34*  ==========
35*
36*> \param[in] N
37*> \verbatim
38*>          N is INTEGTER
39*>          The order of the matrix A.
40*> \endverbatim
41*>
42*> \param[in] NRHS
43*> \verbatim
44*>          NRHS is INTEGER
45*>          The number of right hand sides, i.e., the number of columns
46*>          of the matrices B and X.  NRHS >= 0.
47*> \endverbatim
48*>
49*> \param[in] D
50*> \verbatim
51*>          D is REAL array, dimension (N)
52*>          The n diagonal elements of the tridiagonal matrix A.
53*> \endverbatim
54*>
55*> \param[in] E
56*> \verbatim
57*>          E is REAL array, dimension (N-1)
58*>          The (n-1) subdiagonal elements of the tridiagonal matrix A.
59*> \endverbatim
60*>
61*> \param[in] X
62*> \verbatim
63*>          X is REAL array, dimension (LDX,NRHS)
64*>          The n by nrhs matrix of solution vectors X.
65*> \endverbatim
66*>
67*> \param[in] LDX
68*> \verbatim
69*>          LDX is INTEGER
70*>          The leading dimension of the array X.  LDX >= max(1,N).
71*> \endverbatim
72*>
73*> \param[in,out] B
74*> \verbatim
75*>          B is REAL array, dimension (LDB,NRHS)
76*>          On entry, the n by nrhs matrix of right hand side vectors B.
77*>          On exit, B is overwritten with the difference B - A*X.
78*> \endverbatim
79*>
80*> \param[in] LDB
81*> \verbatim
82*>          LDB is INTEGER
83*>          The leading dimension of the array B.  LDB >= max(1,N).
84*> \endverbatim
85*>
86*> \param[out] RESID
87*> \verbatim
88*>          RESID is REAL
89*>          norm(B - A*X) / (norm(A) * norm(X) * EPS)
90*> \endverbatim
91*
92*  Authors:
93*  ========
94*
95*> \author Univ. of Tennessee
96*> \author Univ. of California Berkeley
97*> \author Univ. of Colorado Denver
98*> \author NAG Ltd.
99*
100*> \date November 2011
101*
102*> \ingroup single_lin
103*
104*  =====================================================================
105      SUBROUTINE SPTT02( N, NRHS, D, E, X, LDX, B, LDB, RESID )
106*
107*  -- LAPACK test routine (version 3.4.0) --
108*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
109*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
110*     November 2011
111*
112*     .. Scalar Arguments ..
113      INTEGER            LDB, LDX, N, NRHS
114      REAL               RESID
115*     ..
116*     .. Array Arguments ..
117      REAL               B( LDB, * ), D( * ), E( * ), X( LDX, * )
118*     ..
119*
120*  =====================================================================
121*
122*     .. Parameters ..
123      REAL               ONE, ZERO
124      PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
125*     ..
126*     .. Local Scalars ..
127      INTEGER            J
128      REAL               ANORM, BNORM, EPS, XNORM
129*     ..
130*     .. External Functions ..
131      REAL               SASUM, SLAMCH, SLANST
132      EXTERNAL           SASUM, SLAMCH, SLANST
133*     ..
134*     .. Intrinsic Functions ..
135      INTRINSIC          MAX
136*     ..
137*     .. External Subroutines ..
138      EXTERNAL           SLAPTM
139*     ..
140*     .. Executable Statements ..
141*
142*     Quick return if possible
143*
144      IF( N.LE.0 ) THEN
145         RESID = ZERO
146         RETURN
147      END IF
148*
149*     Compute the 1-norm of the tridiagonal matrix A.
150*
151      ANORM = SLANST( '1', N, D, E )
152*
153*     Exit with RESID = 1/EPS if ANORM = 0.
154*
155      EPS = SLAMCH( 'Epsilon' )
156      IF( ANORM.LE.ZERO ) THEN
157         RESID = ONE / EPS
158         RETURN
159      END IF
160*
161*     Compute B - A*X.
162*
163      CALL SLAPTM( N, NRHS, -ONE, D, E, X, LDX, ONE, B, LDB )
164*
165*     Compute the maximum over the number of right hand sides of
166*        norm(B - A*X) / ( norm(A) * norm(X) * EPS ).
167*
168      RESID = ZERO
169      DO 10 J = 1, NRHS
170         BNORM = SASUM( N, B( 1, J ), 1 )
171         XNORM = SASUM( N, X( 1, J ), 1 )
172         IF( XNORM.LE.ZERO ) THEN
173            RESID = ONE / EPS
174         ELSE
175            RESID = MAX( RESID, ( ( BNORM / ANORM ) / XNORM ) / EPS )
176         END IF
177   10 CONTINUE
178*
179      RETURN
180*
181*     End of SPTT02
182*
183      END
184