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