LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dgtt05.f
Go to the documentation of this file.
1 *> \brief \b DGTT05
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 DGTT05( TRANS, N, NRHS, DL, D, DU, B, LDB, X, LDX,
12 * XACT, LDXACT, FERR, BERR, RESLTS )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER TRANS
16 * INTEGER LDB, LDX, LDXACT, N, NRHS
17 * ..
18 * .. Array Arguments ..
19 * DOUBLE PRECISION B( LDB, * ), BERR( * ), D( * ), DL( * ),
20 * $ DU( * ), FERR( * ), RESLTS( * ), X( LDX, * ),
21 * $ XACT( LDXACT, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> DGTT05 tests the error bounds from iterative refinement for the
31 *> computed solution to a system of equations A*X = B, where A is a
32 *> general tridiagonal matrix of order n and op(A) = A or A**T,
33 *> depending on TRANS.
34 *>
35 *> RESLTS(1) = test of the error bound
36 *> = norm(X - XACT) / ( norm(X) * FERR )
37 *>
38 *> A large value is returned if this ratio is not less than one.
39 *>
40 *> RESLTS(2) = residual from the iterative refinement routine
41 *> = the maximum of BERR / ( NZ*EPS + (*) ), where
42 *> (*) = NZ*UNFL / (min_i (abs(op(A))*abs(X) +abs(b))_i )
43 *> and NZ = max. number of nonzeros in any row of A, plus 1
44 *> \endverbatim
45 *
46 * Arguments:
47 * ==========
48 *
49 *> \param[in] TRANS
50 *> \verbatim
51 *> TRANS is CHARACTER*1
52 *> Specifies the form of the system of equations.
53 *> = 'N': A * X = B (No transpose)
54 *> = 'T': A**T * X = B (Transpose)
55 *> = 'C': A**H * X = B (Conjugate transpose = Transpose)
56 *> \endverbatim
57 *>
58 *> \param[in] N
59 *> \verbatim
60 *> N is INTEGER
61 *> The number of rows of the matrices X and XACT. N >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in] NRHS
65 *> \verbatim
66 *> NRHS is INTEGER
67 *> The number of columns of the matrices X and XACT. NRHS >= 0.
68 *> \endverbatim
69 *>
70 *> \param[in] DL
71 *> \verbatim
72 *> DL is DOUBLE PRECISION array, dimension (N-1)
73 *> The (n-1) sub-diagonal elements of A.
74 *> \endverbatim
75 *>
76 *> \param[in] D
77 *> \verbatim
78 *> D is DOUBLE PRECISION array, dimension (N)
79 *> The diagonal elements of A.
80 *> \endverbatim
81 *>
82 *> \param[in] DU
83 *> \verbatim
84 *> DU is DOUBLE PRECISION array, dimension (N-1)
85 *> The (n-1) super-diagonal elements of A.
86 *> \endverbatim
87 *>
88 *> \param[in] B
89 *> \verbatim
90 *> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
91 *> The right hand side vectors for the system of linear
92 *> equations.
93 *> \endverbatim
94 *>
95 *> \param[in] LDB
96 *> \verbatim
97 *> LDB is INTEGER
98 *> The leading dimension of the array B. LDB >= max(1,N).
99 *> \endverbatim
100 *>
101 *> \param[in] X
102 *> \verbatim
103 *> X is DOUBLE PRECISION array, dimension (LDX,NRHS)
104 *> The computed solution vectors. Each vector is stored as a
105 *> column of the matrix X.
106 *> \endverbatim
107 *>
108 *> \param[in] LDX
109 *> \verbatim
110 *> LDX is INTEGER
111 *> The leading dimension of the array X. LDX >= max(1,N).
112 *> \endverbatim
113 *>
114 *> \param[in] XACT
115 *> \verbatim
116 *> XACT is DOUBLE PRECISION array, dimension (LDX,NRHS)
117 *> The exact solution vectors. Each vector is stored as a
118 *> column of the matrix XACT.
119 *> \endverbatim
120 *>
121 *> \param[in] LDXACT
122 *> \verbatim
123 *> LDXACT is INTEGER
124 *> The leading dimension of the array XACT. LDXACT >= max(1,N).
125 *> \endverbatim
126 *>
127 *> \param[in] FERR
128 *> \verbatim
129 *> FERR is DOUBLE PRECISION array, dimension (NRHS)
130 *> The estimated forward error bounds for each solution vector
131 *> X. If XTRUE is the true solution, FERR bounds the magnitude
132 *> of the largest entry in (X - XTRUE) divided by the magnitude
133 *> of the largest entry in X.
134 *> \endverbatim
135 *>
136 *> \param[in] BERR
137 *> \verbatim
138 *> BERR is DOUBLE PRECISION array, dimension (NRHS)
139 *> The componentwise relative backward error of each solution
140 *> vector (i.e., the smallest relative change in any entry of A
141 *> or B that makes X an exact solution).
142 *> \endverbatim
143 *>
144 *> \param[out] RESLTS
145 *> \verbatim
146 *> RESLTS is DOUBLE PRECISION array, dimension (2)
147 *> The maximum over the NRHS solution vectors of the ratios:
148 *> RESLTS(1) = norm(X - XACT) / ( norm(X) * FERR )
149 *> RESLTS(2) = BERR / ( NZ*EPS + (*) )
150 *> \endverbatim
151 *
152 * Authors:
153 * ========
154 *
155 *> \author Univ. of Tennessee
156 *> \author Univ. of California Berkeley
157 *> \author Univ. of Colorado Denver
158 *> \author NAG Ltd.
159 *
160 *> \date November 2011
161 *
162 *> \ingroup double_lin
163 *
164 * =====================================================================
165  SUBROUTINE dgtt05( TRANS, N, NRHS, DL, D, DU, B, LDB, X, LDX,
166  $ xact, ldxact, ferr, berr, reslts )
167 *
168 * -- LAPACK test routine (version 3.4.0) --
169 * -- LAPACK is a software package provided by Univ. of Tennessee, --
170 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
171 * November 2011
172 *
173 * .. Scalar Arguments ..
174  CHARACTER trans
175  INTEGER ldb, ldx, ldxact, n, nrhs
176 * ..
177 * .. Array Arguments ..
178  DOUBLE PRECISION b( ldb, * ), berr( * ), d( * ), dl( * ),
179  $ du( * ), ferr( * ), reslts( * ), x( ldx, * ),
180  $ xact( ldxact, * )
181 * ..
182 *
183 * =====================================================================
184 *
185 * .. Parameters ..
186  DOUBLE PRECISION zero, one
187  parameter( zero = 0.0d+0, one = 1.0d+0 )
188 * ..
189 * .. Local Scalars ..
190  LOGICAL notran
191  INTEGER i, imax, j, k, nz
192  DOUBLE PRECISION axbi, diff, eps, errbnd, ovfl, tmp, unfl, xnorm
193 * ..
194 * .. External Functions ..
195  LOGICAL lsame
196  INTEGER idamax
197  DOUBLE PRECISION dlamch
198  EXTERNAL lsame, idamax, dlamch
199 * ..
200 * .. Intrinsic Functions ..
201  INTRINSIC abs, max, min
202 * ..
203 * .. Executable Statements ..
204 *
205 * Quick exit if N = 0 or NRHS = 0.
206 *
207  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
208  reslts( 1 ) = zero
209  reslts( 2 ) = zero
210  return
211  END IF
212 *
213  eps = dlamch( 'Epsilon' )
214  unfl = dlamch( 'Safe minimum' )
215  ovfl = one / unfl
216  notran = lsame( trans, 'N' )
217  nz = 4
218 *
219 * Test 1: Compute the maximum of
220 * norm(X - XACT) / ( norm(X) * FERR )
221 * over all the vectors X and XACT using the infinity-norm.
222 *
223  errbnd = zero
224  DO 30 j = 1, nrhs
225  imax = idamax( n, x( 1, j ), 1 )
226  xnorm = max( abs( x( imax, j ) ), unfl )
227  diff = zero
228  DO 10 i = 1, n
229  diff = max( diff, abs( x( i, j )-xact( i, j ) ) )
230  10 continue
231 *
232  IF( xnorm.GT.one ) THEN
233  go to 20
234  ELSE IF( diff.LE.ovfl*xnorm ) THEN
235  go to 20
236  ELSE
237  errbnd = one / eps
238  go to 30
239  END IF
240 *
241  20 continue
242  IF( diff / xnorm.LE.ferr( j ) ) THEN
243  errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
244  ELSE
245  errbnd = one / eps
246  END IF
247  30 continue
248  reslts( 1 ) = errbnd
249 *
250 * Test 2: Compute the maximum of BERR / ( NZ*EPS + (*) ), where
251 * (*) = NZ*UNFL / (min_i (abs(op(A))*abs(X) +abs(b))_i )
252 *
253  DO 60 k = 1, nrhs
254  IF( notran ) THEN
255  IF( n.EQ.1 ) THEN
256  axbi = abs( b( 1, k ) ) + abs( d( 1 )*x( 1, k ) )
257  ELSE
258  axbi = abs( b( 1, k ) ) + abs( d( 1 )*x( 1, k ) ) +
259  $ abs( du( 1 )*x( 2, k ) )
260  DO 40 i = 2, n - 1
261  tmp = abs( b( i, k ) ) + abs( dl( i-1 )*x( i-1, k ) )
262  $ + abs( d( i )*x( i, k ) ) +
263  $ abs( du( i )*x( i+1, k ) )
264  axbi = min( axbi, tmp )
265  40 continue
266  tmp = abs( b( n, k ) ) + abs( dl( n-1 )*x( n-1, k ) ) +
267  $ abs( d( n )*x( n, k ) )
268  axbi = min( axbi, tmp )
269  END IF
270  ELSE
271  IF( n.EQ.1 ) THEN
272  axbi = abs( b( 1, k ) ) + abs( d( 1 )*x( 1, k ) )
273  ELSE
274  axbi = abs( b( 1, k ) ) + abs( d( 1 )*x( 1, k ) ) +
275  $ abs( dl( 1 )*x( 2, k ) )
276  DO 50 i = 2, n - 1
277  tmp = abs( b( i, k ) ) + abs( du( i-1 )*x( i-1, k ) )
278  $ + abs( d( i )*x( i, k ) ) +
279  $ abs( dl( i )*x( i+1, k ) )
280  axbi = min( axbi, tmp )
281  50 continue
282  tmp = abs( b( n, k ) ) + abs( du( n-1 )*x( n-1, k ) ) +
283  $ abs( d( n )*x( n, k ) )
284  axbi = min( axbi, tmp )
285  END IF
286  END IF
287  tmp = berr( k ) / ( nz*eps+nz*unfl / max( axbi, nz*unfl ) )
288  IF( k.EQ.1 ) THEN
289  reslts( 2 ) = tmp
290  ELSE
291  reslts( 2 ) = max( reslts( 2 ), tmp )
292  END IF
293  60 continue
294 *
295  return
296 *
297 * End of DGTT05
298 *
299  END