1*> \brief \b DPPT05
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 DPPT05( UPLO, N, NRHS, AP, B, LDB, X, LDX, XACT,
12*                          LDXACT, FERR, BERR, RESLTS )
13*
14*       .. Scalar Arguments ..
15*       CHARACTER          UPLO
16*       INTEGER            LDB, LDX, LDXACT, N, NRHS
17*       ..
18*       .. Array Arguments ..
19*       DOUBLE PRECISION   AP( * ), B( LDB, * ), BERR( * ), FERR( * ),
20*      $                   RESLTS( * ), X( LDX, * ), XACT( LDXACT, * )
21*       ..
22*
23*
24*> \par Purpose:
25*  =============
26*>
27*> \verbatim
28*>
29*> DPPT05 tests the error bounds from iterative refinement for the
30*> computed solution to a system of equations A*X = B, where A is a
31*> symmetric matrix in packed storage format.
32*>
33*> RESLTS(1) = test of the error bound
34*>           = norm(X - XACT) / ( norm(X) * FERR )
35*>
36*> A large value is returned if this ratio is not less than one.
37*>
38*> RESLTS(2) = residual from the iterative refinement routine
39*>           = the maximum of BERR / ( (n+1)*EPS + (*) ), where
40*>             (*) = (n+1)*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
41*> \endverbatim
42*
43*  Arguments:
44*  ==========
45*
46*> \param[in] UPLO
47*> \verbatim
48*>          UPLO is CHARACTER*1
49*>          Specifies whether the upper or lower triangular part of the
50*>          symmetric matrix A is stored.
51*>          = 'U':  Upper triangular
52*>          = 'L':  Lower triangular
53*> \endverbatim
54*>
55*> \param[in] N
56*> \verbatim
57*>          N is INTEGER
58*>          The number of rows of the matrices X, B, and XACT, and the
59*>          order of the matrix A.  N >= 0.
60*> \endverbatim
61*>
62*> \param[in] NRHS
63*> \verbatim
64*>          NRHS is INTEGER
65*>          The number of columns of the matrices X, B, and XACT.
66*>          NRHS >= 0.
67*> \endverbatim
68*>
69*> \param[in] AP
70*> \verbatim
71*>          AP is DOUBLE PRECISION array, dimension (N*(N+1)/2)
72*>          The upper or lower triangle of the symmetric matrix A, packed
73*>          columnwise in a linear array.  The j-th column of A is stored
74*>          in the array AP as follows:
75*>          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
76*>          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
77*> \endverbatim
78*>
79*> \param[in] B
80*> \verbatim
81*>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
82*>          The right hand side vectors for the system of linear
83*>          equations.
84*> \endverbatim
85*>
86*> \param[in] LDB
87*> \verbatim
88*>          LDB is INTEGER
89*>          The leading dimension of the array B.  LDB >= max(1,N).
90*> \endverbatim
91*>
92*> \param[in] X
93*> \verbatim
94*>          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
95*>          The computed solution vectors.  Each vector is stored as a
96*>          column of the matrix X.
97*> \endverbatim
98*>
99*> \param[in] LDX
100*> \verbatim
101*>          LDX is INTEGER
102*>          The leading dimension of the array X.  LDX >= max(1,N).
103*> \endverbatim
104*>
105*> \param[in] XACT
106*> \verbatim
107*>          XACT is DOUBLE PRECISION array, dimension (LDX,NRHS)
108*>          The exact solution vectors.  Each vector is stored as a
109*>          column of the matrix XACT.
110*> \endverbatim
111*>
112*> \param[in] LDXACT
113*> \verbatim
114*>          LDXACT is INTEGER
115*>          The leading dimension of the array XACT.  LDXACT >= max(1,N).
116*> \endverbatim
117*>
118*> \param[in] FERR
119*> \verbatim
120*>          FERR is DOUBLE PRECISION array, dimension (NRHS)
121*>          The estimated forward error bounds for each solution vector
122*>          X.  If XTRUE is the true solution, FERR bounds the magnitude
123*>          of the largest entry in (X - XTRUE) divided by the magnitude
124*>          of the largest entry in X.
125*> \endverbatim
126*>
127*> \param[in] BERR
128*> \verbatim
129*>          BERR is DOUBLE PRECISION array, dimension (NRHS)
130*>          The componentwise relative backward error of each solution
131*>          vector (i.e., the smallest relative change in any entry of A
132*>          or B that makes X an exact solution).
133*> \endverbatim
134*>
135*> \param[out] RESLTS
136*> \verbatim
137*>          RESLTS is DOUBLE PRECISION array, dimension (2)
138*>          The maximum over the NRHS solution vectors of the ratios:
139*>          RESLTS(1) = norm(X - XACT) / ( norm(X) * FERR )
140*>          RESLTS(2) = BERR / ( (n+1)*EPS + (*) )
141*> \endverbatim
142*
143*  Authors:
144*  ========
145*
146*> \author Univ. of Tennessee
147*> \author Univ. of California Berkeley
148*> \author Univ. of Colorado Denver
149*> \author NAG Ltd.
150*
151*> \date December 2016
152*
153*> \ingroup double_lin
154*
155*  =====================================================================
156      SUBROUTINE DPPT05( UPLO, N, NRHS, AP, B, LDB, X, LDX, XACT,
157     $                   LDXACT, FERR, BERR, RESLTS )
158*
159*  -- LAPACK test routine (version 3.7.0) --
160*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
161*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162*     December 2016
163*
164*     .. Scalar Arguments ..
165      CHARACTER          UPLO
166      INTEGER            LDB, LDX, LDXACT, N, NRHS
167*     ..
168*     .. Array Arguments ..
169      DOUBLE PRECISION   AP( * ), B( LDB, * ), BERR( * ), FERR( * ),
170     $                   RESLTS( * ), X( LDX, * ), XACT( LDXACT, * )
171*     ..
172*
173*  =====================================================================
174*
175*     .. Parameters ..
176      DOUBLE PRECISION   ZERO, ONE
177      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
178*     ..
179*     .. Local Scalars ..
180      LOGICAL            UPPER
181      INTEGER            I, IMAX, J, JC, K
182      DOUBLE PRECISION   AXBI, DIFF, EPS, ERRBND, OVFL, TMP, UNFL, XNORM
183*     ..
184*     .. External Functions ..
185      LOGICAL            LSAME
186      INTEGER            IDAMAX
187      DOUBLE PRECISION   DLAMCH
188      EXTERNAL           LSAME, IDAMAX, DLAMCH
189*     ..
190*     .. Intrinsic Functions ..
191      INTRINSIC          ABS, MAX, MIN
192*     ..
193*     .. Executable Statements ..
194*
195*     Quick exit if N = 0 or NRHS = 0.
196*
197      IF( N.LE.0 .OR. NRHS.LE.0 ) THEN
198         RESLTS( 1 ) = ZERO
199         RESLTS( 2 ) = ZERO
200         RETURN
201      END IF
202*
203      EPS = DLAMCH( 'Epsilon' )
204      UNFL = DLAMCH( 'Safe minimum' )
205      OVFL = ONE / UNFL
206      UPPER = LSAME( UPLO, 'U' )
207*
208*     Test 1:  Compute the maximum of
209*        norm(X - XACT) / ( norm(X) * FERR )
210*     over all the vectors X and XACT using the infinity-norm.
211*
212      ERRBND = ZERO
213      DO 30 J = 1, NRHS
214         IMAX = IDAMAX( N, X( 1, J ), 1 )
215         XNORM = MAX( ABS( X( IMAX, J ) ), UNFL )
216         DIFF = ZERO
217         DO 10 I = 1, N
218            DIFF = MAX( DIFF, ABS( X( I, J )-XACT( I, J ) ) )
219   10    CONTINUE
220*
221         IF( XNORM.GT.ONE ) THEN
222            GO TO 20
223         ELSE IF( DIFF.LE.OVFL*XNORM ) THEN
224            GO TO 20
225         ELSE
226            ERRBND = ONE / EPS
227            GO TO 30
228         END IF
229*
230   20    CONTINUE
231         IF( DIFF / XNORM.LE.FERR( J ) ) THEN
232            ERRBND = MAX( ERRBND, ( DIFF / XNORM ) / FERR( J ) )
233         ELSE
234            ERRBND = ONE / EPS
235         END IF
236   30 CONTINUE
237      RESLTS( 1 ) = ERRBND
238*
239*     Test 2:  Compute the maximum of BERR / ( (n+1)*EPS + (*) ), where
240*     (*) = (n+1)*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
241*
242      DO 90 K = 1, NRHS
243         DO 80 I = 1, N
244            TMP = ABS( B( I, K ) )
245            IF( UPPER ) THEN
246               JC = ( ( I-1 )*I ) / 2
247               DO 40 J = 1, I
248                  TMP = TMP + ABS( AP( JC+J ) )*ABS( X( J, K ) )
249   40          CONTINUE
250               JC = JC + I
251               DO 50 J = I + 1, N
252                  TMP = TMP + ABS( AP( JC ) )*ABS( X( J, K ) )
253                  JC = JC + J
254   50          CONTINUE
255            ELSE
256               JC = I
257               DO 60 J = 1, I - 1
258                  TMP = TMP + ABS( AP( JC ) )*ABS( X( J, K ) )
259                  JC = JC + N - J
260   60          CONTINUE
261               DO 70 J = I, N
262                  TMP = TMP + ABS( AP( JC+J-I ) )*ABS( X( J, K ) )
263   70          CONTINUE
264            END IF
265            IF( I.EQ.1 ) THEN
266               AXBI = TMP
267            ELSE
268               AXBI = MIN( AXBI, TMP )
269            END IF
270   80    CONTINUE
271         TMP = BERR( K ) / ( ( N+1 )*EPS+( N+1 )*UNFL /
272     $         MAX( AXBI, ( N+1 )*UNFL ) )
273         IF( K.EQ.1 ) THEN
274            RESLTS( 2 ) = TMP
275         ELSE
276            RESLTS( 2 ) = MAX( RESLTS( 2 ), TMP )
277         END IF
278   90 CONTINUE
279*
280      RETURN
281*
282*     End of DPPT05
283*
284      END
285