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