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