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