1CPOSVXX(1) LAPACK driver routine (version 3.2) CPOSVXX(1)
2
3
4
6 CPOSVXX - CPOSVXX use the Cholesky factorization A = U**T*U or A =
7 L*L**T to compute the solution to a complex system of linear equations
8 A * X = B, where A is an N-by-N symmetric positive definite matrix and
9 X and B are N-by-NRHS matrices
10
12 SUBROUTINE CPOSVXX( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, EQUED, S, B,
13 LDB, X, LDX, RCOND, RPVGRW, BERR, N_ERR_BNDS,
14 ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS,
15 WORK, RWORK, INFO )
16
17 IMPLICIT NONE
18
19 CHARACTER EQUED, FACT, UPLO
20
21 INTEGER INFO, LDA, LDAF, LDB, LDX, N, NRHS, NPARAMS,
22 N_ERR_BNDS
23
24 REAL RCOND, RPVGRW
25
26 COMPLEX A( LDA, * ), AF( LDAF, * ), B( LDB, * ), WORK( * ),
27 X( LDX, * )
28
29 REAL S( * ), PARAMS( * ), BERR( * ), RWORK( * ),
30 ERR_BNDS_NORM( NRHS, * ), ERR_BNDS_COMP( NRHS, * )
31
33 CPOSVXX uses the Cholesky factorization A = U**T*U or A = L*L**T
34 to compute the solution to a complex system of linear equations
35 A * X = B, where A is an N-by-N symmetric positive definite matrix
36 and X and B are N-by-NRHS matrices.
37 If requested, both normwise and maximum componentwise error bounds
38 are returned. CPOSVXX will return a solution with a tiny
39 guaranteed error (O(eps) where eps is the working machine
40 precision) unless the matrix is very ill-conditioned, in which
41 case a warning is returned. Relevant condition numbers also are
42 calculated and returned.
43 CPOSVXX accepts user-provided factorizations and equilibration
44 factors; see the definitions of the FACT and EQUED options.
45 Solving with refinement and using a factorization from a previous
46 CPOSVXX call will also produce a solution with either O(eps)
47 errors or warnings, but we cannot make that claim for general
48 user-provided factorizations and equilibration factors if they
49 differ from what CPOSVXX would itself produce.
50
52 The following steps are performed:
53 1. If FACT = 'E', real scaling factors are computed to equilibrate
54 the system:
55 diag(S)*A*diag(S) *inv(diag(S))*X = diag(S)*B
56 Whether or not the system will be equilibrated depends on the
57 scaling of the matrix A, but if equilibration is used, A is
58 overwritten by diag(S)*A*diag(S) and B by diag(S)*B.
59 2. If FACT = 'N' or 'E', the Cholesky decomposition is used to
60 factor the matrix A (after equilibration if FACT = 'E') as
61 A = U**T* U, if UPLO = 'U', or
62 A = L * L**T, if UPLO = 'L',
63 where U is an upper triangular matrix and L is a lower triangular
64 matrix.
65 3. If the leading i-by-i principal minor is not positive definite,
66 then the routine returns with INFO = i. Otherwise, the factored
67 form of A is used to estimate the condition number of the matrix
68 A (see argument RCOND). If the reciprocal of the condition number
69 is less than machine precision, the routine still goes on to solve
70 for X and compute error bounds as described below.
71 4. The system of equations is solved for X using the factored form
72 of A.
73 5. By default (unless PARAMS(LA_LINRX_ITREF_I) is set to zero),
74 the routine will use iterative refinement to try to get a small
75 error and error bounds. Refinement calculates the residual to at
76 least twice the working precision.
77 6. If equilibration was used, the matrix X is premultiplied by
78 diag(S) so that it solves the original system before
79 equilibration.
80
82 Some optional parameters are bundled in the PARAMS array. These set‐
83 tings determine how refinement is performed, but often the defaults are
84 acceptable. If the defaults are acceptable, users can pass NPARAMS = 0
85 which prevents the source code from accessing the PARAMS argument.
86
87 FACT (input) CHARACTER*1
88 Specifies whether or not the factored form of the matrix A is
89 supplied on entry, and if not, whether the matrix A should be
90 equilibrated before it is factored. = 'F': On entry, AF con‐
91 tains the factored form of A. If EQUED is not 'N', the matrix
92 A has been equilibrated with scaling factors given by S. A and
93 AF are not modified. = 'N': The matrix A will be copied to AF
94 and factored.
95 = 'E': The matrix A will be equilibrated if necessary, then
96 copied to AF and factored.
97
98 UPLO (input) CHARACTER*1
99 = 'U': Upper triangle of A is stored;
100 = 'L': Lower triangle of A is stored.
101
102 N (input) INTEGER
103 The number of linear equations, i.e., the order of the matrix
104 A. N >= 0.
105
106 NRHS (input) INTEGER
107 The number of right hand sides, i.e., the number of columns of
108 the matrices B and X. NRHS >= 0.
109
110 A (input/output) COMPLEX array, dimension (LDA,N)
111 On entry, the symmetric matrix A, except if FACT = 'F' and
112 EQUED = 'Y', then A must contain the equilibrated matrix
113 diag(S)*A*diag(S). If UPLO = 'U', the leading N-by-N upper
114 triangular part of A contains the upper triangular part of the
115 matrix A, and the strictly lower triangular part of A is not
116 referenced. If UPLO = 'L', the leading N-by-N lower triangular
117 part of A contains the lower triangular part of the matrix A,
118 and the strictly upper triangular part of A is not referenced.
119 A is not modified if FACT = 'F' or 'N', or if FACT = 'E' and
120 EQUED = 'N' on exit. On exit, if FACT = 'E' and EQUED = 'Y', A
121 is overwritten by diag(S)*A*diag(S).
122
123 LDA (input) INTEGER
124 The leading dimension of the array A. LDA >= max(1,N).
125
126 AF (input or output) COMPLEX array, dimension (LDAF,N)
127 If FACT = 'F', then AF is an input argument and on entry con‐
128 tains the triangular factor U or L from the Cholesky factoriza‐
129 tion A = U**T*U or A = L*L**T, in the same storage format as A.
130 If EQUED .ne. 'N', then AF is the factored form of the equili‐
131 brated matrix diag(S)*A*diag(S). If FACT = 'N', then AF is an
132 output argument and on exit returns the triangular factor U or
133 L from the Cholesky factorization A = U**T*U or A = L*L**T of
134 the original matrix A. If FACT = 'E', then AF is an output
135 argument and on exit returns the triangular factor U or L from
136 the Cholesky factorization A = U**T*U or A = L*L**T of the
137 equilibrated matrix A (see the description of A for the form of
138 the equilibrated matrix).
139
140 LDAF (input) INTEGER
141 The leading dimension of the array AF. LDAF >= max(1,N).
142
143 EQUED (input or output) CHARACTER*1
144 Specifies the form of equilibration that was done. = 'N': No
145 equilibration (always true if FACT = 'N').
146 = 'Y': Both row and column equilibration, i.e., A has been
147 replaced by diag(S) * A * diag(S). EQUED is an input argument
148 if FACT = 'F'; otherwise, it is an output argument.
149
150 S (input or output) REAL array, dimension (N)
151 The row scale factors for A. If EQUED = 'Y', A is multiplied
152 on the left and right by diag(S). S is an input argument if
153 FACT = 'F'; otherwise, S is an output argument. If FACT = 'F'
154 and EQUED = 'Y', each element of S must be positive. If S is
155 output, each element of S is a power of the radix. If S is
156 input, each element of S should be a power of the radix to
157 ensure a reliable solution and error estimates. Scaling by pow‐
158 ers of the radix does not cause rounding errors unless the
159 result underflows or overflows. Rounding errors during scaling
160 lead to refining with a matrix that is not equivalent to the
161 input matrix, producing error estimates that may not be reli‐
162 able.
163
164 B (input/output) COMPLEX array, dimension (LDB,NRHS)
165 On entry, the N-by-NRHS right hand side matrix B. On exit, if
166 EQUED = 'N', B is not modified; if EQUED = 'Y', B is overwrit‐
167 ten by diag(S)*B;
168
169 LDB (input) INTEGER
170 The leading dimension of the array B. LDB >= max(1,N).
171
172 X (output) COMPLEX array, dimension (LDX,NRHS)
173 If INFO = 0, the N-by-NRHS solution matrix X to the original
174 system of equations. Note that A and B are modified on exit if
175 EQUED .ne. 'N', and the solution to the equilibrated system is
176 inv(diag(S))*X.
177
178 LDX (input) INTEGER
179 The leading dimension of the array X. LDX >= max(1,N).
180
181 RCOND (output) REAL
182 Reciprocal scaled condition number. This is an estimate of the
183 reciprocal Skeel condition number of the matrix A after equili‐
184 bration (if done). If this is less than the machine precision
185 (in particular, if it is zero), the matrix is singular to work‐
186 ing precision. Note that the error may still be small even if
187 this number is very small and the matrix appears ill- condi‐
188 tioned.
189
190 RPVGRW (output) REAL
191 Reciprocal pivot growth. On exit, this contains the reciprocal
192 pivot growth factor norm(A)/norm(U). The "max absolute element"
193 norm is used. If this is much less than 1, then the stability
194 of the LU factorization of the (equilibrated) matrix A could be
195 poor. This also means that the solution X, estimated condition
196 numbers, and error bounds could be unreliable. If factorization
197 fails with 0<INFO<=N, then this contains the reciprocal pivot
198 growth factor for the leading INFO columns of A.
199
200 BERR (output) REAL array, dimension (NRHS)
201 Componentwise relative backward error. This is the component‐
202 wise relative backward error of each solution vector X(j)
203 (i.e., the smallest relative change in any element of A or B
204 that makes X(j) an exact solution). N_ERR_BNDS (input) INTEGER
205 Number of error bounds to return for each right hand side and
206 each type (normwise or componentwise). See ERR_BNDS_NORM and
207 ERR_BNDS_COMP below.
208
209 ERR_BNDS_NORM (output) REAL array, dimension (NRHS, N_ERR_BNDS)
210 For each right-hand side, this array contains informa‐
211 tion about various error bounds and condition numbers
212 corresponding to the normwise relative error, which is
213 defined as follows: Normwise relative error in the ith
214 solution vector: max_j (abs(XTRUE(j,i) - X(j,i)))
215 ------------------------------ max_j abs(X(j,i)) The
216 array is indexed by the type of error information as
217 described below. There currently are up to three pieces
218 of information returned. The first index in
219 ERR_BNDS_NORM(i,:) corresponds to the ith right-hand
220 side. The second index in ERR_BNDS_NORM(:,err) contains
221 the following three fields: err = 1 "Trust/don't trust"
222 boolean. Trust the answer if the reciprocal condition
223 number is less than the threshold sqrt(n) *
224 slamch('Epsilon'). err = 2 "Guaranteed" error bound:
225 The estimated forward error, almost certainly within a
226 factor of 10 of the true error so long as the next entry
227 is greater than the threshold sqrt(n) *
228 slamch('Epsilon'). This error bound should only be
229 trusted if the previous boolean is true. err = 3
230 Reciprocal condition number: Estimated normwise recipro‐
231 cal condition number. Compared with the threshold
232 sqrt(n) * slamch('Epsilon') to determine if the error
233 estimate is "guaranteed". These reciprocal condition
234 numbers are 1 / (norm(Z^{-1},inf) * norm(Z,inf)) for
235 some appropriately scaled matrix Z. Let Z = S*A, where
236 S scales each row by a power of the radix so all abso‐
237 lute row sums of Z are approximately 1. See Lapack
238 Working Note 165 for further details and extra cautions.
239
240 ERR_BNDS_COMP (output) REAL array, dimension (NRHS, N_ERR_BNDS)
241 For each right-hand side, this array contains informa‐
242 tion about various error bounds and condition numbers
243 corresponding to the componentwise relative error, which
244 is defined as follows: Componentwise relative error in
245 the ith solution vector: abs(XTRUE(j,i) - X(j,i)) max_j
246 ---------------------- abs(X(j,i)) The array is indexed
247 by the right-hand side i (on which the componentwise
248 relative error depends), and the type of error informa‐
249 tion as described below. There currently are up to three
250 pieces of information returned for each right-hand side.
251 If componentwise accuracy is not requested (PARAMS(3) =
252 0.0), then ERR_BNDS_COMP is not accessed. If N_ERR_BNDS
253 .LT. 3, then at most the first (:,N_ERR_BNDS) entries
254 are returned. The first index in ERR_BNDS_COMP(i,:)
255 corresponds to the ith right-hand side. The second
256 index in ERR_BNDS_COMP(:,err) contains the following
257 three fields: err = 1 "Trust/don't trust" boolean. Trust
258 the answer if the reciprocal condition number is less
259 than the threshold sqrt(n) * slamch('Epsilon'). err = 2
260 "Guaranteed" error bound: The estimated forward error,
261 almost certainly within a factor of 10 of the true error
262 so long as the next entry is greater than the threshold
263 sqrt(n) * slamch('Epsilon'). This error bound should
264 only be trusted if the previous boolean is true. err =
265 3 Reciprocal condition number: Estimated componentwise
266 reciprocal condition number. Compared with the thresh‐
267 old sqrt(n) * slamch('Epsilon') to determine if the
268 error estimate is "guaranteed". These reciprocal condi‐
269 tion numbers are 1 / (norm(Z^{-1},inf) * norm(Z,inf))
270 for some appropriately scaled matrix Z. Let Z =
271 S*(A*diag(x)), where x is the solution for the current
272 right-hand side and S scales each row of A*diag(x) by a
273 power of the radix so all absolute row sums of Z are
274 approximately 1. See Lapack Working Note 165 for fur‐
275 ther details and extra cautions. NPARAMS (input) INTE‐
276 GER Specifies the number of parameters set in PARAMS.
277 If .LE. 0, the PARAMS array is never referenced and
278 default values are used.
279
280 PARAMS (input / output) REAL array, dimension NPARAMS
281 Specifies algorithm parameters. If an entry is .LT. 0.0, then
282 that entry will be filled with default value used for that
283 parameter. Only positions up to NPARAMS are accessed; defaults
284 are used for higher-numbered parameters.
285 PARAMS(LA_LINRX_ITREF_I = 1) : Whether to perform iterative
286 refinement or not. Default: 1.0
287 = 0.0 : No refinement is performed, and no error bounds are
288 computed. = 1.0 : Use the double-precision refinement algo‐
289 rithm, possibly with doubled-single computations if the compi‐
290 lation environment does not support DOUBLE PRECISION. (other
291 values are reserved for future use) PARAMS(LA_LINRX_ITHRESH_I =
292 2) : Maximum number of residual computations allowed for
293 refinement. Default: 10
294 Aggressive: Set to 100 to permit convergence using approximate
295 factorizations or factorizations other than LU. If the factor‐
296 ization uses a technique other than Gaussian elimination, the
297 guarantees in err_bnds_norm and err_bnds_comp may no longer be
298 trustworthy. PARAMS(LA_LINRX_CWISE_I = 3) : Flag determining
299 if the code will attempt to find a solution with small compo‐
300 nentwise relative error in the double-precision algorithm.
301 Positive is true, 0.0 is false. Default: 1.0 (attempt compo‐
302 nentwise convergence)
303
304 WORK (workspace) REAL array, dimension (4*N)
305
306 IWORK (workspace) INTEGER array, dimension (N)
307
308 INFO (output) INTEGER
309 = 0: Successful exit. The solution to every right-hand side is
310 guaranteed. < 0: If INFO = -i, the i-th argument had an ille‐
311 gal value
312 > 0 and <= N: U(INFO,INFO) is exactly zero. The factorization
313 has been completed, but the factor U is exactly singular, so
314 the solution and error bounds could not be computed. RCOND = 0
315 is returned. = N+J: The solution corresponding to the Jth
316 right-hand side is not guaranteed. The solutions corresponding
317 to other right- hand sides K with K > J may not be guaranteed
318 as well, but only the first such right-hand side is reported.
319 If a small componentwise error is not requested (PARAMS(3) =
320 0.0) then the Jth right-hand side is the first with a normwise
321 error bound that is not guaranteed (the smallest J such that
322 ERR_BNDS_NORM(J,1) = 0.0). By default (PARAMS(3) = 1.0) the Jth
323 right-hand side is the first with either a normwise or compo‐
324 nentwise error bound that is not guaranteed (the smallest J
325 such that either ERR_BNDS_NORM(J,1) = 0.0 or ERR_BNDS_COMP(J,1)
326 = 0.0). See the definition of ERR_BNDS_NORM(:,1) and
327 ERR_BNDS_COMP(:,1). To get information about all of the right-
328 hand sides check ERR_BNDS_NORM or ERR_BNDS_COMP.
329
330
331
332 LAPACK driver routine (versionNo3v.e2m)ber 2008 CPOSVXX(1)