1ZGBRFSX(1) LAPACK routine (version 3.2) ZGBRFSX(1)
2
3
4
6 ZGBRFSX - ZGBRFSX improve the computed solution to a system of linear
7 equations and provides error bounds and backward error estimates for
8 the solution
9
11 SUBROUTINE ZGBRFSX( TRANS, EQUED, N, KL, KU, NRHS, AB, LDAB, AFB,
12 LDAFB, IPIV, R, C, B, LDB, X, LDX, RCOND, BERR,
13 N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS,
14 PARAMS, WORK, RWORK, INFO )
15
16 IMPLICIT NONE
17
18 CHARACTER TRANS, EQUED
19
20 INTEGER INFO, LDAB, LDAFB, LDB, LDX, N, KL, KU, NRHS,
21 NPARAMS, N_ERR_BNDS
22
23 DOUBLE PRECISION RCOND
24
25 INTEGER IPIV( * )
26
27 COMPLEX*16 AB( LDAB, * ), AFB( LDAFB, * ), B( LDB, * ), X( LDX
28 , * ),WORK( * )
29
30 DOUBLE PRECISION R( * ), C( * ), PARAMS( * ), BERR( * ),
31 ERR_BNDS_NORM( NRHS, * ), ERR_BNDS_COMP( NRHS, * ),
32 RWORK( * )
33
35 ZGBRFSX improves the computed solution to a system of linear
36 equations and provides error bounds and backward error estimates
37 for the solution. In addition to normwise error bound, the code
38 provides maximum componentwise error bound if possible. See
39 comments for ERR_BNDS_N and ERR_BNDS_C for details of the error
40 bounds.
41 The original system of linear equations may have been equilibrated
42 before calling this routine, as described by arguments EQUED, R
43 and C below. In this case, the solution and error bounds returned
44 are for the original unequilibrated system.
45
47 Some optional parameters are bundled in the PARAMS array. These set‐
48 tings determine how refinement is performed, but often the defaults are
49 acceptable. If the defaults are acceptable, users can pass NPARAMS = 0
50 which prevents the source code from accessing the PARAMS argument.
51
52 TRANS (input) CHARACTER*1
53 Specifies the form of the system of equations:
54 = 'N': A * X = B (No transpose)
55 = 'T': A**T * X = B (Transpose)
56 = 'C': A**H * X = B (Conjugate transpose = Transpose)
57
58 EQUED (input) CHARACTER*1
59 Specifies the form of equilibration that was done to A before
60 calling this routine. This is needed to compute the solution
61 and error bounds correctly. = 'N': No equilibration
62 = 'R': Row equilibration, i.e., A has been premultiplied by
63 diag(R). = 'C': Column equilibration, i.e., A has been post‐
64 multiplied by diag(C). = 'B': Both row and column equilibra‐
65 tion, i.e., A has been replaced by diag(R) * A * diag(C). The
66 right hand side B has been changed accordingly.
67
68 N (input) INTEGER
69 The order of the matrix A. N >= 0.
70
71 KL (input) INTEGER
72 The number of subdiagonals within the band of A. KL >= 0.
73
74 KU (input) INTEGER
75 The number of superdiagonals within the band of A. KU >= 0.
76
77 NRHS (input) INTEGER
78 The number of right hand sides, i.e., the number of columns of
79 the matrices B and X. NRHS >= 0.
80
81 AB (input) DOUBLE PRECISION array, dimension (LDAB,N)
82 The original band matrix A, stored in rows 1 to KL+KU+1. The
83 j-th column of A is stored in the j-th column of the array AB
84 as follows: AB(ku+1+i-j,j) = A(i,j) for max(1,j-
85 ku)<=i<=min(n,j+kl).
86
87 LDAB (input) INTEGER
88 The leading dimension of the array AB. LDAB >= KL+KU+1.
89
90 AFB (input) DOUBLE PRECISION array, dimension (LDAFB,N)
91 Details of the LU factorization of the band matrix A, as com‐
92 puted by DGBTRF. U is stored as an upper triangular band
93 matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and the
94 multipliers used during the factorization are stored in rows
95 KL+KU+2 to 2*KL+KU+1.
96
97 LDAFB (input) INTEGER
98 The leading dimension of the array AFB. LDAFB >= 2*KL*KU+1.
99
100 IPIV (input) INTEGER array, dimension (N)
101 The pivot indices from DGETRF; for 1<=i<=N, row i of the matrix
102 was interchanged with row IPIV(i).
103
104 R (input or output) DOUBLE PRECISION array, dimension (N)
105 The row scale factors for A. If EQUED = 'R' or 'B', A is mul‐
106 tiplied on the left by diag(R); if EQUED = 'N' or 'C', R is not
107 accessed. R is an input argument if FACT = 'F'; otherwise, R
108 is an output argument. If FACT = 'F' and EQUED = 'R' or 'B',
109 each element of R must be positive. If R is output, each ele‐
110 ment of R is a power of the radix. If R is input, each element
111 of R should be a power of the radix to ensure a reliable solu‐
112 tion and error estimates. Scaling by powers of the radix does
113 not cause rounding errors unless the result underflows or over‐
114 flows. Rounding errors during scaling lead to refining with a
115 matrix that is not equivalent to the input matrix, producing
116 error estimates that may not be reliable.
117
118 C (input or output) DOUBLE PRECISION array, dimension (N)
119 The column scale factors for A. If EQUED = 'C' or 'B', A is
120 multiplied on the right by diag(C); if EQUED = 'N' or 'R', C is
121 not accessed. C is an input argument if FACT = 'F'; otherwise,
122 C is an output argument. If FACT = 'F' and EQUED = 'C' or 'B',
123 each element of C must be positive. If C is output, each ele‐
124 ment of C is a power of the radix. If C is input, each element
125 of C should be a power of the radix to ensure a reliable solu‐
126 tion and error estimates. Scaling by powers of the radix does
127 not cause rounding errors unless the result underflows or over‐
128 flows. Rounding errors during scaling lead to refining with a
129 matrix that is not equivalent to the input matrix, producing
130 error estimates that may not be reliable.
131
132 B (input) DOUBLE PRECISION array, dimension (LDB,NRHS)
133 The right hand side matrix B.
134
135 LDB (input) INTEGER
136 The leading dimension of the array B. LDB >= max(1,N).
137
138 X (input/output) DOUBLE PRECISION array, dimension (LDX,NRHS)
139 On entry, the solution matrix X, as computed by DGETRS. On
140 exit, the improved solution matrix X.
141
142 LDX (input) INTEGER
143 The leading dimension of the array X. LDX >= max(1,N).
144
145 RCOND (output) DOUBLE PRECISION
146 Reciprocal scaled condition number. This is an estimate of the
147 reciprocal Skeel condition number of the matrix A after equili‐
148 bration (if done). If this is less than the machine precision
149 (in particular, if it is zero), the matrix is singular to work‐
150 ing precision. Note that the error may still be small even if
151 this number is very small and the matrix appears ill- condi‐
152 tioned.
153
154 BERR (output) DOUBLE PRECISION array, dimension (NRHS)
155 Componentwise relative backward error. This is the component‐
156 wise relative backward error of each solution vector X(j)
157 (i.e., the smallest relative change in any element of A or B
158 that makes X(j) an exact solution). N_ERR_BNDS (input) INTEGER
159 Number of error bounds to return for each right hand side and
160 each type (normwise or componentwise). See ERR_BNDS_NORM and
161 ERR_BNDS_COMP below.
162
163 ERR_BNDS_NORM (output) DOUBLE PRECISION array, dimension (NRHS,
164 N_ERR_BNDS)
165 For each right-hand side, this array contains informa‐
166 tion about various error bounds and condition numbers
167 corresponding to the normwise relative error, which is
168 defined as follows: Normwise relative error in the ith
169 solution vector: max_j (abs(XTRUE(j,i) - X(j,i)))
170 ------------------------------ max_j abs(X(j,i)) The
171 array is indexed by the type of error information as
172 described below. There currently are up to three pieces
173 of information returned. The first index in
174 ERR_BNDS_NORM(i,:) corresponds to the ith right-hand
175 side. The second index in ERR_BNDS_NORM(:,err) contains
176 the following three fields: err = 1 "Trust/don't trust"
177 boolean. Trust the answer if the reciprocal condition
178 number is less than the threshold sqrt(n) *
179 dlamch('Epsilon'). err = 2 "Guaranteed" error bound:
180 The estimated forward error, almost certainly within a
181 factor of 10 of the true error so long as the next entry
182 is greater than the threshold sqrt(n) *
183 dlamch('Epsilon'). This error bound should only be
184 trusted if the previous boolean is true. err = 3
185 Reciprocal condition number: Estimated normwise recipro‐
186 cal condition number. Compared with the threshold
187 sqrt(n) * dlamch('Epsilon') to determine if the error
188 estimate is "guaranteed". These reciprocal condition
189 numbers are 1 / (norm(Z^{-1},inf) * norm(Z,inf)) for
190 some appropriately scaled matrix Z. Let Z = S*A, where
191 S scales each row by a power of the radix so all abso‐
192 lute row sums of Z are approximately 1. See Lapack
193 Working Note 165 for further details and extra cautions.
194
195 ERR_BNDS_COMP (output) DOUBLE PRECISION array, dimension (NRHS,
196 N_ERR_BNDS)
197 For each right-hand side, this array contains informa‐
198 tion about various error bounds and condition numbers
199 corresponding to the componentwise relative error, which
200 is defined as follows: Componentwise relative error in
201 the ith solution vector: abs(XTRUE(j,i) - X(j,i)) max_j
202 ---------------------- abs(X(j,i)) The array is indexed
203 by the right-hand side i (on which the componentwise
204 relative error depends), and the type of error informa‐
205 tion as described below. There currently are up to three
206 pieces of information returned for each right-hand side.
207 If componentwise accuracy is not requested (PARAMS(3) =
208 0.0), then ERR_BNDS_COMP is not accessed. If N_ERR_BNDS
209 .LT. 3, then at most the first (:,N_ERR_BNDS) entries
210 are returned. The first index in ERR_BNDS_COMP(i,:)
211 corresponds to the ith right-hand side. The second
212 index in ERR_BNDS_COMP(:,err) contains the following
213 three fields: err = 1 "Trust/don't trust" boolean. Trust
214 the answer if the reciprocal condition number is less
215 than the threshold sqrt(n) * dlamch('Epsilon'). err = 2
216 "Guaranteed" error bound: The estimated forward error,
217 almost certainly within a factor of 10 of the true error
218 so long as the next entry is greater than the threshold
219 sqrt(n) * dlamch('Epsilon'). This error bound should
220 only be trusted if the previous boolean is true. err =
221 3 Reciprocal condition number: Estimated componentwise
222 reciprocal condition number. Compared with the thresh‐
223 old sqrt(n) * dlamch('Epsilon') to determine if the
224 error estimate is "guaranteed". These reciprocal condi‐
225 tion numbers are 1 / (norm(Z^{-1},inf) * norm(Z,inf))
226 for some appropriately scaled matrix Z. Let Z =
227 S*(A*diag(x)), where x is the solution for the current
228 right-hand side and S scales each row of A*diag(x) by a
229 power of the radix so all absolute row sums of Z are
230 approximately 1. See Lapack Working Note 165 for fur‐
231 ther details and extra cautions. NPARAMS (input) INTE‐
232 GER Specifies the number of parameters set in PARAMS.
233 If .LE. 0, the PARAMS array is never referenced and
234 default values are used.
235
236 PARAMS (input / output) DOUBLE PRECISION array, dimension NPARAMS
237 Specifies algorithm parameters. If an entry is .LT. 0.0, then
238 that entry will be filled with default value used for that
239 parameter. Only positions up to NPARAMS are accessed; defaults
240 are used for higher-numbered parameters.
241 PARAMS(LA_LINRX_ITREF_I = 1) : Whether to perform iterative
242 refinement or not. Default: 1.0D+0
243 = 0.0 : No refinement is performed, and no error bounds are
244 computed. = 1.0 : Use the double-precision refinement algo‐
245 rithm, possibly with doubled-single computations if the compi‐
246 lation environment does not support DOUBLE PRECISION. (other
247 values are reserved for future use) PARAMS(LA_LINRX_ITHRESH_I =
248 2) : Maximum number of residual computations allowed for
249 refinement. Default: 10
250 Aggressive: Set to 100 to permit convergence using approximate
251 factorizations or factorizations other than LU. If the factor‐
252 ization uses a technique other than Gaussian elimination, the
253 guarantees in err_bnds_norm and err_bnds_comp may no longer be
254 trustworthy. PARAMS(LA_LINRX_CWISE_I = 3) : Flag determining
255 if the code will attempt to find a solution with small compo‐
256 nentwise relative error in the double-precision algorithm.
257 Positive is true, 0.0 is false. Default: 1.0 (attempt compo‐
258 nentwise convergence)
259
260 WORK (workspace) DOUBLE PRECISION array, dimension (4*N)
261
262 IWORK (workspace) INTEGER array, dimension (N)
263
264 INFO (output) INTEGER
265 = 0: Successful exit. The solution to every right-hand side is
266 guaranteed. < 0: If INFO = -i, the i-th argument had an ille‐
267 gal value
268 > 0 and <= N: U(INFO,INFO) is exactly zero. The factorization
269 has been completed, but the factor U is exactly singular, so
270 the solution and error bounds could not be computed. RCOND = 0
271 is returned. = N+J: The solution corresponding to the Jth
272 right-hand side is not guaranteed. The solutions corresponding
273 to other right- hand sides K with K > J may not be guaranteed
274 as well, but only the first such right-hand side is reported.
275 If a small componentwise error is not requested (PARAMS(3) =
276 0.0) then the Jth right-hand side is the first with a normwise
277 error bound that is not guaranteed (the smallest J such that
278 ERR_BNDS_NORM(J,1) = 0.0). By default (PARAMS(3) = 1.0) the Jth
279 right-hand side is the first with either a normwise or compo‐
280 nentwise error bound that is not guaranteed (the smallest J
281 such that either ERR_BNDS_NORM(J,1) = 0.0 or ERR_BNDS_COMP(J,1)
282 = 0.0). See the definition of ERR_BNDS_NORM(:,1) and
283 ERR_BNDS_COMP(:,1). To get information about all of the right-
284 hand sides check ERR_BNDS_NORM or ERR_BNDS_COMP.
285
286
287
288 LAPACK routine (version 3.2) November 2008 ZGBRFSX(1)