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