1CSYSVX(1) LAPACK driver routine (version 3.1) CSYSVX(1)
2
3
4
6 CSYSVX - the diagonal pivoting factorization to compute the solution to
7 a complex system of linear equations A * X = B,
8
10 SUBROUTINE CSYSVX( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB,
11 X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO
12 )
13
14 CHARACTER FACT, UPLO
15
16 INTEGER INFO, LDA, LDAF, LDB, LDX, LWORK, N, NRHS
17
18 REAL RCOND
19
20 INTEGER IPIV( * )
21
22 REAL BERR( * ), FERR( * ), RWORK( * )
23
24 COMPLEX A( LDA, * ), AF( LDAF, * ), B( LDB, * ), WORK( * ),
25 X( LDX, * )
26
28 CSYSVX uses the diagonal pivoting factorization to compute the solution
29 to a complex system of linear equations A * X = B, where A is an N-by-N
30 symmetric matrix and X and B are N-by-NRHS matrices.
31
32 Error bounds on the solution and a condition estimate are also pro‐
33 vided.
34
35
37 The following steps are performed:
38
39 1. If FACT = 'N', the diagonal pivoting method is used to factor A.
40 The form of the factorization is
41 A = U * D * U**T, if UPLO = 'U', or
42 A = L * D * L**T, if UPLO = 'L',
43 where U (or L) is a product of permutation and unit upper (lower)
44 triangular matrices, and D is symmetric and block diagonal with
45 1-by-1 and 2-by-2 diagonal blocks.
46
47 2. If some D(i,i)=0, so that D is exactly singular, then the routine
48 returns with INFO = i. Otherwise, the factored form of A is used
49 to estimate the condition number of the matrix A. If the
50 reciprocal of the condition number is less than machine precision,
51 INFO = N+1 is returned as a warning, but the routine still goes on
52 to solve for X and compute error bounds as described below.
53
54 3. The system of equations is solved for X using the factored form
55 of A.
56
57 4. Iterative refinement is applied to improve the computed solution
58 matrix and calculate error bounds and backward error estimates
59 for it.
60
61
63 FACT (input) CHARACTER*1
64 Specifies whether or not the factored form of A has been sup‐
65 plied on entry. = 'F': On entry, AF and IPIV contain the fac‐
66 tored form of A. A, AF and IPIV will not be modified. = 'N':
67 The matrix A will be copied to AF and factored.
68
69 UPLO (input) CHARACTER*1
70 = 'U': Upper triangle of A is stored;
71 = 'L': Lower triangle of A is stored.
72
73 N (input) INTEGER
74 The number of linear equations, i.e., the order of the matrix
75 A. N >= 0.
76
77 NRHS (input) INTEGER
78 The number of right hand sides, i.e., the number of columns of
79 the matrices B and X. NRHS >= 0.
80
81 A (input) COMPLEX array, dimension (LDA,N)
82 The symmetric matrix A. If UPLO = 'U', the leading N-by-N
83 upper triangular part of A contains the upper triangular part
84 of the matrix A, and the strictly lower triangular part of A is
85 not referenced. If UPLO = 'L', the leading N-by-N lower trian‐
86 gular part of A contains the lower triangular part of the
87 matrix A, and the strictly upper triangular part of A is not
88 referenced.
89
90 LDA (input) INTEGER
91 The leading dimension of the array A. LDA >= max(1,N).
92
93 AF (input or output) COMPLEX array, dimension (LDAF,N)
94 If FACT = 'F', then AF is an input argument and on entry con‐
95 tains the block diagonal matrix D and the multipliers used to
96 obtain the factor U or L from the factorization A = U*D*U**T or
97 A = L*D*L**T as computed by CSYTRF.
98
99 If FACT = 'N', then AF is an output argument and on exit
100 returns the block diagonal matrix D and the multipliers used to
101 obtain the factor U or L from the factorization A = U*D*U**T or
102 A = L*D*L**T.
103
104 LDAF (input) INTEGER
105 The leading dimension of the array AF. LDAF >= max(1,N).
106
107 IPIV (input or output) INTEGER array, dimension (N)
108 If FACT = 'F', then IPIV is an input argument and on entry con‐
109 tains details of the interchanges and the block structure of D,
110 as determined by CSYTRF. If IPIV(k) > 0, then rows and columns
111 k and IPIV(k) were interchanged and D(k,k) is a 1-by-1 diagonal
112 block. If UPLO = 'U' and IPIV(k) = IPIV(k-1) < 0, then rows
113 and columns k-1 and -IPIV(k) were interchanged and
114 D(k-1:k,k-1:k) is a 2-by-2 diagonal block. If UPLO = 'L' and
115 IPIV(k) = IPIV(k+1) < 0, then rows and columns k+1 and -IPIV(k)
116 were interchanged and D(k:k+1,k:k+1) is a 2-by-2 diagonal
117 block.
118
119 If FACT = 'N', then IPIV is an output argument and on exit con‐
120 tains details of the interchanges and the block structure of D,
121 as determined by CSYTRF.
122
123 B (input) COMPLEX array, dimension (LDB,NRHS)
124 The N-by-NRHS right hand side matrix B.
125
126 LDB (input) INTEGER
127 The leading dimension of the array B. LDB >= max(1,N).
128
129 X (output) COMPLEX array, dimension (LDX,NRHS)
130 If INFO = 0 or INFO = N+1, the N-by-NRHS solution matrix X.
131
132 LDX (input) INTEGER
133 The leading dimension of the array X. LDX >= max(1,N).
134
135 RCOND (output) REAL
136 The estimate of the reciprocal condition number of the matrix
137 A. If RCOND is less than the machine precision (in particular,
138 if RCOND = 0), the matrix is singular to working precision.
139 This condition is indicated by a return code of INFO > 0.
140
141 FERR (output) REAL array, dimension (NRHS)
142 The estimated forward error bound for each solution vector X(j)
143 (the j-th column of the solution matrix X). If XTRUE is the
144 true solution corresponding to X(j), FERR(j) is an estimated
145 upper bound for the magnitude of the largest element in (X(j) -
146 XTRUE) divided by the magnitude of the largest element in X(j).
147 The estimate is as reliable as the estimate for RCOND, and is
148 almost always a slight overestimate of the true error.
149
150 BERR (output) REAL array, dimension (NRHS)
151 The componentwise relative backward error of each solution vec‐
152 tor X(j) (i.e., the smallest relative change in any element of
153 A or B that makes X(j) an exact solution).
154
155 WORK (workspace/output) COMPLEX array, dimension (MAX(1,LWORK))
156 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
157
158 LWORK (input) INTEGER
159 The length of WORK. LWORK >= max(1,2*N), and for best perfor‐
160 mance, when FACT = 'N', LWORK >= max(1,2*N,N*NB), where NB is
161 the optimal blocksize for CSYTRF.
162
163 If LWORK = -1, then a workspace query is assumed; the routine
164 only calculates the optimal size of the WORK array, returns
165 this value as the first entry of the WORK array, and no error
166 message related to LWORK is issued by XERBLA.
167
168 RWORK (workspace) REAL array, dimension (N)
169
170 INFO (output) INTEGER
171 = 0: successful exit
172 < 0: if INFO = -i, the i-th argument had an illegal value
173 > 0: if INFO = i, and i is
174 <= N: D(i,i) is exactly zero. The factorization has been com‐
175 pleted but the factor D is exactly singular, so the solution
176 and error bounds could not be computed. RCOND = 0 is returned.
177 = N+1: D is nonsingular, but RCOND is less than machine preci‐
178 sion, meaning that the matrix is singular to working precision.
179 Nevertheless, the solution and error bounds are computed
180 because there are a number of situations where the computed
181 solution can be more accurate than the value of RCOND would
182 suggest.
183
184
185
186 LAPACK driver routine (version 3.N1o)vember 2006 CSYSVX(1)