1DGBSVX(1)             LAPACK driver routine (version 3.1)            DGBSVX(1)
2
3
4

NAME

6       DGBSVX  - the LU factorization to compute the solution to a real system
7       of linear equations A * X = B, A**T * X = B, or A**H * X = B,
8

SYNOPSIS

10       SUBROUTINE DGBSVX( FACT, TRANS, N, KL, KU, NRHS, AB, LDAB, AFB,  LDAFB,
11                          IPIV,  EQUED,  R,  C,  B,  LDB, X, LDX, RCOND, FERR,
12                          BERR, WORK, IWORK, INFO )
13
14           CHARACTER      EQUED, FACT, TRANS
15
16           INTEGER        INFO, KL, KU, LDAB, LDAFB, LDB, LDX, N, NRHS
17
18           DOUBLE         PRECISION RCOND
19
20           INTEGER        IPIV( * ), IWORK( * )
21
22           DOUBLE         PRECISION AB( LDAB, * ), AFB( LDAFB, * ), B( LDB,  *
23                          ),  BERR( * ), C( * ), FERR( * ), R( * ), WORK( * ),
24                          X( LDX, * )
25

PURPOSE

27       DGBSVX uses the LU factorization to compute the solution to a real sys‐
28       tem of linear equations A * X = B, A**T * X = B, or A**H * X = B, where
29       A is a band matrix of order N with KL subdiagonals and  KU  superdiago‐
30       nals, 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

DESCRIPTION

37       The following steps are performed by this subroutine:
38
39       1. If FACT = 'E', real scaling factors are computed to equilibrate
40          the system:
41             TRANS = 'N':  diag(R)*A*diag(C)     *inv(diag(C))*X = diag(R)*B
42             TRANS = 'T': (diag(R)*A*diag(C))**T *inv(diag(R))*X = diag(C)*B
43             TRANS = 'C': (diag(R)*A*diag(C))**H *inv(diag(R))*X = diag(C)*B
44          Whether or not the system will be equilibrated depends on the
45          scaling of the matrix A, but if equilibration is used, A is
46          overwritten by diag(R)*A*diag(C) and B by diag(R)*B (if TRANS='N')
47          or diag(C)*B (if TRANS = 'T' or 'C').
48
49       2. If FACT = 'N' or 'E', the LU decomposition is used to factor the
50          matrix A (after equilibration if FACT = 'E') as
51             A = L * U,
52          where L is a product of permutation and unit lower triangular
53          matrices with KL subdiagonals, and U is upper triangular with
54          KL+KU superdiagonals.
55
56       3. If some U(i,i)=0, so that U is exactly singular, then the routine
57          returns with INFO = i. Otherwise, the factored form of A is used
58          to estimate the condition number of the matrix A.  If the
59          reciprocal of the condition number is less than machine precision,
60          INFO = N+1 is returned as a warning, but the routine still goes on
61          to solve for X and compute error bounds as described below.
62
63       4. The system of equations is solved for X using the factored form
64          of A.
65
66       5. Iterative refinement is applied to improve the computed solution
67          matrix and calculate error bounds and backward error estimates
68          for it.
69
70       6. If equilibration was used, the matrix X is premultiplied by
71          diag(C) (if TRANS = 'N') or diag(R) (if TRANS = 'T' or 'C') so
72          that it solves the original system before equilibration.
73
74

ARGUMENTS

76       FACT    (input) CHARACTER*1
77               Specifies whether or not the factored form of the matrix  A  is
78               supplied  on  entry, and if not, whether the matrix A should be
79               equilibrated before it is factored.  = 'F':  On entry, AFB  and
80               IPIV  contain the factored form of A.  If EQUED is not 'N', the
81               matrix A has been equilibrated with scaling factors given by  R
82               and C.  AB, AFB, and IPIV are not modified.  = 'N':  The matrix
83               A will be copied to AFB and factored.
84               = 'E':  The matrix A will be equilibrated  if  necessary,  then
85               copied to AFB and factored.
86
87       TRANS   (input) CHARACTER*1
88               Specifies the form of the system of equations.  = 'N':  A * X =
89               B     (No transpose)
90               = 'T':  A**T * X = B  (Transpose)
91               = 'C':  A**H * X = B  (Transpose)
92
93       N       (input) INTEGER
94               The number of linear equations, i.e., the order of  the  matrix
95               A.  N >= 0.
96
97       KL      (input) INTEGER
98               The number of subdiagonals within the band of A.  KL >= 0.
99
100       KU      (input) INTEGER
101               The number of superdiagonals within the band of A.  KU >= 0.
102
103       NRHS    (input) INTEGER
104               The  number of right hand sides, i.e., the number of columns of
105               the matrices B and X.  NRHS >= 0.
106
107       AB      (input/output) DOUBLE PRECISION array, dimension (LDAB,N)
108               On entry, the matrix A in band storage, in rows 1  to  KL+KU+1.
109               The  j-th column of A is stored in the j-th column of the array
110               AB  as  follows:   AB(KU+1+i-j,j)   =   A(i,j)   for   max(1,j-
111               KU)<=i<=min(N,j+kl)
112
113               If FACT = 'F' and EQUED is not 'N', then A must have been equi‐
114               librated by the scaling factors in R and/or C.  AB is not modi‐
115               fied  if FACT = 'F' or 'N', or if FACT = 'E' and EQUED = 'N' on
116               exit.
117
118               On exit, if EQUED .ne. 'N', A is scaled  as  follows:  EQUED  =
119               'R':  A := diag(R) * A
120               EQUED = 'C':  A := A * diag(C)
121               EQUED = 'B':  A := diag(R) * A * diag(C).
122
123       LDAB    (input) INTEGER
124               The leading dimension of the array AB.  LDAB >= KL+KU+1.
125
126       AFB     (input or output) DOUBLE PRECISION array, dimension (LDAFB,N)
127               If  FACT = 'F', then AFB is an input argument and on entry con‐
128               tains details of the LU factorization of the band matrix A,  as
129               computed  by  DGBTRF.   U is stored as an upper triangular band
130               matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and  the
131               multipliers  used  during  the factorization are stored in rows
132               KL+KU+2 to 2*KL+KU+1.  If EQUED .ne. 'N', then AFB is the  fac‐
133               tored form of the equilibrated matrix A.
134
135               If  FACT  =  'N',  then  AFB  is an output argument and on exit
136               returns details of the LU factorization of A.
137
138               If FACT = 'E', then AFB is  an  output  argument  and  on  exit
139               returns  details  of  the  LU factorization of the equilibrated
140               matrix A (see the description of AB for the form of the equili‐
141               brated matrix).
142
143       LDAFB   (input) INTEGER
144               The leading dimension of the array AFB.  LDAFB >= 2*KL+KU+1.
145
146       IPIV    (input or output) INTEGER array, dimension (N)
147               If FACT = 'F', then IPIV is an input argument and on entry con‐
148               tains the pivot indices from the factorization A = L*U as  com‐
149               puted  by DGBTRF; row i of the matrix was interchanged with row
150               IPIV(i).
151
152               If FACT = 'N', then IPIV is an output argument and on exit con‐
153               tains  the  pivot indices from the factorization A = L*U of the
154               original matrix A.
155
156               If FACT = 'E', then IPIV is an output argument and on exit con‐
157               tains  the  pivot indices from the factorization A = L*U of the
158               equilibrated matrix A.
159
160       EQUED   (input or output) CHARACTER*1
161               Specifies the form of equilibration that was done.  = 'N':   No
162               equilibration (always true if FACT = 'N').
163               =  'R':   Row  equilibration, i.e., A has been premultiplied by
164               diag(R).  = 'C':  Column equilibration, i.e., A has been  post‐
165               multiplied  by diag(C).  = 'B':  Both row and column equilibra‐
166               tion, i.e., A has been replaced  by  diag(R)  *  A  *  diag(C).
167               EQUED  is  an input argument if FACT = 'F'; otherwise, it is an
168               output argument.
169
170       R       (input or output) DOUBLE PRECISION array, dimension (N)
171               The row scale factors for A.  If EQUED = 'R' or 'B', A is  mul‐
172               tiplied on the left by diag(R); if EQUED = 'N' or 'C', R is not
173               accessed.  R is an input argument if FACT = 'F';  otherwise,  R
174               is  an  output argument.  If FACT = 'F' and EQUED = 'R' or 'B',
175               each element of R must be positive.
176
177       C       (input or output) DOUBLE PRECISION array, dimension (N)
178               The column scale factors for A.  If EQUED = 'C' or  'B',  A  is
179               multiplied on the right by diag(C); if EQUED = 'N' or 'R', C is
180               not accessed.  C is an input argument if FACT = 'F'; otherwise,
181               C is an output argument.  If FACT = 'F' and EQUED = 'C' or 'B',
182               each element of C must be positive.
183
184       B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
185               On entry, the right hand side matrix B.  On exit,  if  EQUED  =
186               'N',  B is not modified; if TRANS = 'N' and EQUED = 'R' or 'B',
187               B is overwritten by diag(R)*B; if TRANS = 'T' or 'C' and  EQUED
188               = 'C' or 'B', B is overwritten by diag(C)*B.
189
190       LDB     (input) INTEGER
191               The leading dimension of the array B.  LDB >= max(1,N).
192
193       X       (output) DOUBLE PRECISION array, dimension (LDX,NRHS)
194               If  INFO  = 0 or INFO = N+1, the N-by-NRHS solution matrix X to
195               the original system of equations.  Note that A and B are  modi‐
196               fied on exit if EQUED .ne. 'N', and the solution to the equili‐
197               brated system is inv(diag(C))*X if TRANS = 'N' and EQUED =  'C'
198               or 'B', or inv(diag(R))*X if TRANS = 'T' or 'C' and EQUED = 'R'
199               or 'B'.
200
201       LDX     (input) INTEGER
202               The leading dimension of the array X.  LDX >= max(1,N).
203
204       RCOND   (output) DOUBLE PRECISION
205               The estimate of the reciprocal condition number of the matrix A
206               after  equilibration  (if  done).   If  RCOND  is less than the
207               machine precision (in particular, if RCOND = 0), the matrix  is
208               singular  to working precision.  This condition is indicated by
209               a return code of INFO > 0.
210
211       FERR    (output) DOUBLE PRECISION array, dimension (NRHS)
212               The estimated forward error bound for each solution vector X(j)
213               (the  j-th  column  of the solution matrix X).  If XTRUE is the
214               true solution corresponding to X(j), FERR(j)  is  an  estimated
215               upper bound for the magnitude of the largest element in (X(j) -
216               XTRUE) divided by the magnitude of the largest element in X(j).
217               The  estimate  is as reliable as the estimate for RCOND, and is
218               almost always a slight overestimate of the true error.
219
220       BERR    (output) DOUBLE PRECISION array, dimension (NRHS)
221               The componentwise relative backward error of each solution vec‐
222               tor  X(j) (i.e., the smallest relative change in any element of
223               A or B that makes X(j) an exact solution).
224
225       WORK    (workspace/output) DOUBLE PRECISION array, dimension (3*N)
226               On exit, WORK(1) contains the reciprocal  pivot  growth  factor
227               norm(A)/norm(U).  The  "max  absolute element" norm is used. If
228               WORK(1) is much less than 1, then the stability of the LU  fac‐
229               torization  of  the (equilibrated) matrix A could be poor. This
230               also means that the solution X, condition estimator RCOND,  and
231               forward  error bound FERR could be unreliable. If factorization
232               fails with 0<INFO<=N,  then  WORK(1)  contains  the  reciprocal
233               pivot growth factor for the leading INFO columns of A.
234
235       IWORK   (workspace) INTEGER array, dimension (N)
236
237       INFO    (output) INTEGER
238               = 0:  successful exit
239               < 0:  if INFO = -i, the i-th argument had an illegal value
240               > 0:  if INFO = i, and i is
241               <= N:  U(i,i) is exactly zero.  The factorization has been com‐
242               pleted, but the factor U is exactly singular, so  the  solution
243               and  error bounds could not be computed. RCOND = 0 is returned.
244               = N+1: U is nonsingular, but RCOND is less than machine  preci‐
245               sion, meaning that the matrix is singular to working precision.
246               Nevertheless,  the  solution  and  error  bounds  are  computed
247               because  there  are  a  number of situations where the computed
248               solution can be more accurate than the  value  of  RCOND  would
249               suggest.
250
251
252
253 LAPACK driver routine (version 3.N1o)vember 2006                       DGBSVX(1)
Impressum