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