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