1*> \brief \b DTPT02
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 DTPT02( UPLO, TRANS, DIAG, N, NRHS, AP, X, LDX, B, LDB,
12*                          WORK, RESID )
13*
14*       .. Scalar Arguments ..
15*       CHARACTER          DIAG, TRANS, UPLO
16*       INTEGER            LDB, LDX, N, NRHS
17*       DOUBLE PRECISION   RESID
18*       ..
19*       .. Array Arguments ..
20*       DOUBLE PRECISION   AP( * ), B( LDB, * ), WORK( * ), X( LDX, * )
21*       ..
22*
23*
24*> \par Purpose:
25*  =============
26*>
27*> \verbatim
28*>
29*> DTPT02 computes the residual for the computed solution to a
30*> triangular system of linear equations  A*x = b  or  A'*x = b  when
31*> the triangular matrix A is stored in packed format.  Here A' is the
32*> transpose of A and x and b are N by NRHS matrices.  The test ratio is
33*> the maximum over the number of right hand sides of
34*>    norm(b - op(A)*x) / ( norm(op(A)) * norm(x) * EPS ),
35*> where op(A) denotes A or A' and EPS is the machine epsilon.
36*> The norm used is the 1-norm.
37*> \endverbatim
38*
39*  Arguments:
40*  ==========
41*
42*> \param[in] UPLO
43*> \verbatim
44*>          UPLO is CHARACTER*1
45*>          Specifies whether the matrix A is upper or lower triangular.
46*>          = 'U':  Upper triangular
47*>          = 'L':  Lower triangular
48*> \endverbatim
49*>
50*> \param[in] TRANS
51*> \verbatim
52*>          TRANS is CHARACTER*1
53*>          Specifies the operation applied to A.
54*>          = 'N':  A *x = b  (No transpose)
55*>          = 'T':  A'*x = b  (Transpose)
56*>          = 'C':  A'*x = b  (Conjugate transpose = Transpose)
57*> \endverbatim
58*>
59*> \param[in] DIAG
60*> \verbatim
61*>          DIAG is CHARACTER*1
62*>          Specifies whether or not the matrix A is unit triangular.
63*>          = 'N':  Non-unit triangular
64*>          = 'U':  Unit triangular
65*> \endverbatim
66*>
67*> \param[in] N
68*> \verbatim
69*>          N is INTEGER
70*>          The order of the matrix A.  N >= 0.
71*> \endverbatim
72*>
73*> \param[in] NRHS
74*> \verbatim
75*>          NRHS is INTEGER
76*>          The number of right hand sides, i.e., the number of columns
77*>          of the matrices X and B.  NRHS >= 0.
78*> \endverbatim
79*>
80*> \param[in] AP
81*> \verbatim
82*>          AP is DOUBLE PRECISION array, dimension (N*(N+1)/2)
83*>          The upper or lower triangular matrix A, packed columnwise in
84*>          a linear array.  The j-th column of A is stored in the array
85*>          AP as follows:
86*>          if UPLO = 'U', AP((j-1)*j/2 + i) = A(i,j) for 1<=i<=j;
87*>          if UPLO = 'L',
88*>             AP((j-1)*(n-j) + j*(j+1)/2 + i-j) = A(i,j) for j<=i<=n.
89*> \endverbatim
90*>
91*> \param[in] X
92*> \verbatim
93*>          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
94*>          The computed solution vectors for the system of linear
95*>          equations.
96*> \endverbatim
97*>
98*> \param[in] LDX
99*> \verbatim
100*>          LDX is INTEGER
101*>          The leading dimension of the array X.  LDX >= max(1,N).
102*> \endverbatim
103*>
104*> \param[in] B
105*> \verbatim
106*>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
107*>          The right hand side vectors for the system of linear
108*>          equations.
109*> \endverbatim
110*>
111*> \param[in] LDB
112*> \verbatim
113*>          LDB is INTEGER
114*>          The leading dimension of the array B.  LDB >= max(1,N).
115*> \endverbatim
116*>
117*> \param[out] WORK
118*> \verbatim
119*>          WORK is DOUBLE PRECISION array, dimension (N)
120*> \endverbatim
121*>
122*> \param[out] RESID
123*> \verbatim
124*>          RESID is DOUBLE PRECISION
125*>          The maximum over the number of right hand sides of
126*>          norm(op(A)*x - b) / ( norm(op(A)) * norm(x) * EPS ).
127*> \endverbatim
128*
129*  Authors:
130*  ========
131*
132*> \author Univ. of Tennessee
133*> \author Univ. of California Berkeley
134*> \author Univ. of Colorado Denver
135*> \author NAG Ltd.
136*
137*> \ingroup double_lin
138*
139*  =====================================================================
140      SUBROUTINE DTPT02( UPLO, TRANS, DIAG, N, NRHS, AP, X, LDX, B, LDB,
141     $                   WORK, RESID )
142*
143*  -- LAPACK test routine --
144*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
145*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146*
147*     .. Scalar Arguments ..
148      CHARACTER          DIAG, TRANS, UPLO
149      INTEGER            LDB, LDX, N, NRHS
150      DOUBLE PRECISION   RESID
151*     ..
152*     .. Array Arguments ..
153      DOUBLE PRECISION   AP( * ), B( LDB, * ), WORK( * ), X( LDX, * )
154*     ..
155*
156*  =====================================================================
157*
158*     .. Parameters ..
159      DOUBLE PRECISION   ZERO, ONE
160      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
161*     ..
162*     .. Local Scalars ..
163      INTEGER            J
164      DOUBLE PRECISION   ANORM, BNORM, EPS, XNORM
165*     ..
166*     .. External Functions ..
167      LOGICAL            LSAME
168      DOUBLE PRECISION   DASUM, DLAMCH, DLANTP
169      EXTERNAL           LSAME, DASUM, DLAMCH, DLANTP
170*     ..
171*     .. External Subroutines ..
172      EXTERNAL           DAXPY, DCOPY, DTPMV
173*     ..
174*     .. Intrinsic Functions ..
175      INTRINSIC          MAX
176*     ..
177*     .. Executable Statements ..
178*
179*     Quick exit if N = 0 or NRHS = 0
180*
181      IF( N.LE.0 .OR. NRHS.LE.0 ) THEN
182         RESID = ZERO
183         RETURN
184      END IF
185*
186*     Compute the 1-norm of A or A'.
187*
188      IF( LSAME( TRANS, 'N' ) ) THEN
189         ANORM = DLANTP( '1', UPLO, DIAG, N, AP, WORK )
190      ELSE
191         ANORM = DLANTP( 'I', UPLO, DIAG, N, AP, WORK )
192      END IF
193*
194*     Exit with RESID = 1/EPS if ANORM = 0.
195*
196      EPS = DLAMCH( 'Epsilon' )
197      IF( ANORM.LE.ZERO ) THEN
198         RESID = ONE / EPS
199         RETURN
200      END IF
201*
202*     Compute the maximum over the number of right hand sides of
203*        norm(op(A)*x - b) / ( norm(op(A)) * norm(x) * EPS ).
204*
205      RESID = ZERO
206      DO 10 J = 1, NRHS
207         CALL DCOPY( N, X( 1, J ), 1, WORK, 1 )
208         CALL DTPMV( UPLO, TRANS, DIAG, N, AP, WORK, 1 )
209         CALL DAXPY( N, -ONE, B( 1, J ), 1, WORK, 1 )
210         BNORM = DASUM( N, WORK, 1 )
211         XNORM = DASUM( N, X( 1, J ), 1 )
212         IF( XNORM.LE.ZERO ) THEN
213            RESID = ONE / EPS
214         ELSE
215            RESID = MAX( RESID, ( ( BNORM / ANORM ) / XNORM ) / EPS )
216         END IF
217   10 CONTINUE
218*
219      RETURN
220*
221*     End of DTPT02
222*
223      END
224