LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cpbt05.f
Go to the documentation of this file.
1 *> \brief \b CPBT05
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 CPBT05( 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 BERR( * ), FERR( * ), RESLTS( * )
20 * COMPLEX AB( LDAB, * ), B( LDB, * ), X( LDX, * ),
21 * $ XACT( LDXACT, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> CPBT05 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 *> Hermitian 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 *> Hermitian 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 COMPLEX array, dimension (LDAB,N)
81 *> The upper or lower triangle of the Hermitian 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 COMPLEX 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 COMPLEX 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 COMPLEX 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 complex_lin
169 *
170 * =====================================================================
171  SUBROUTINE cpbt05( 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 BERR( * ), FERR( * ), RESLTS( * )
185  COMPLEX AB( ldab, * ), B( ldb, * ), 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  COMPLEX ZDUM
200 * ..
201 * .. External Functions ..
202  LOGICAL LSAME
203  INTEGER ICAMAX
204  REAL SLAMCH
205  EXTERNAL lsame, icamax, slamch
206 * ..
207 * .. Intrinsic Functions ..
208  INTRINSIC abs, aimag, max, min, real
209 * ..
210 * .. Statement Functions ..
211  REAL CABS1
212 * ..
213 * .. Statement Function definitions ..
214  cabs1( zdum ) = abs( REAL( ZDUM ) ) + abs( AIMAG( zdum ) )
215 * ..
216 * .. Executable Statements ..
217 *
218 * Quick exit if N = 0 or NRHS = 0.
219 *
220  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
221  reslts( 1 ) = zero
222  reslts( 2 ) = zero
223  RETURN
224  END IF
225 *
226  eps = slamch( 'Epsilon' )
227  unfl = slamch( 'Safe minimum' )
228  ovfl = one / unfl
229  upper = lsame( uplo, 'U' )
230  nz = 2*max( kd, n-1 ) + 1
231 *
232 * Test 1: Compute the maximum of
233 * norm(X - XACT) / ( norm(X) * FERR )
234 * over all the vectors X and XACT using the infinity-norm.
235 *
236  errbnd = zero
237  DO 30 j = 1, nrhs
238  imax = icamax( n, x( 1, j ), 1 )
239  xnorm = max( cabs1( x( imax, j ) ), unfl )
240  diff = zero
241  DO 10 i = 1, n
242  diff = max( diff, cabs1( x( i, j )-xact( i, j ) ) )
243  10 CONTINUE
244 *
245  IF( xnorm.GT.one ) THEN
246  GO TO 20
247  ELSE IF( diff.LE.ovfl*xnorm ) THEN
248  GO TO 20
249  ELSE
250  errbnd = one / eps
251  GO TO 30
252  END IF
253 *
254  20 CONTINUE
255  IF( diff / xnorm.LE.ferr( j ) ) THEN
256  errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
257  ELSE
258  errbnd = one / eps
259  END IF
260  30 CONTINUE
261  reslts( 1 ) = errbnd
262 *
263 * Test 2: Compute the maximum of BERR / ( NZ*EPS + (*) ), where
264 * (*) = NZ*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
265 *
266  DO 90 k = 1, nrhs
267  DO 80 i = 1, n
268  tmp = cabs1( b( i, k ) )
269  IF( upper ) THEN
270  DO 40 j = max( i-kd, 1 ), i - 1
271  tmp = tmp + cabs1( ab( kd+1-i+j, i ) )*
272  $ cabs1( x( j, k ) )
273  40 CONTINUE
274  tmp = tmp + abs( REAL( AB( KD+1, I ) ) )*
275  $ cabs1( x( i, k ) )
276  DO 50 j = i + 1, min( i+kd, n )
277  tmp = tmp + cabs1( ab( kd+1+i-j, j ) )*
278  $ cabs1( x( j, k ) )
279  50 CONTINUE
280  ELSE
281  DO 60 j = max( i-kd, 1 ), i - 1
282  tmp = tmp + cabs1( ab( 1+i-j, j ) )*cabs1( x( j, k ) )
283  60 CONTINUE
284  tmp = tmp + abs( REAL( AB( 1, I ) ) )*cabs1( X( i, k ) )
285  DO 70 j = i + 1, min( i+kd, n )
286  tmp = tmp + cabs1( ab( 1+j-i, i ) )*cabs1( x( j, k ) )
287  70 CONTINUE
288  END IF
289  IF( i.EQ.1 ) THEN
290  axbi = tmp
291  ELSE
292  axbi = min( axbi, tmp )
293  END IF
294  80 CONTINUE
295  tmp = berr( k ) / ( nz*eps+nz*unfl / max( axbi, nz*unfl ) )
296  IF( k.EQ.1 ) THEN
297  reslts( 2 ) = tmp
298  ELSE
299  reslts( 2 ) = max( reslts( 2 ), tmp )
300  END IF
301  90 CONTINUE
302 *
303  RETURN
304 *
305 * End of CPBT05
306 *
307  END
subroutine cpbt05(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, X, LDX, XACT, LDXACT, FERR, BERR, RESLTS)
CPBT05
Definition: cpbt05.f:173