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