1SGBSVX(1)             LAPACK driver routine (version 3.2)            SGBSVX(1)
2
3
4

NAME

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

SYNOPSIS

10       SUBROUTINE SGBSVX( 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           REAL           RCOND
19
20           INTEGER        IPIV( * ), IWORK( * )
21
22           REAL           AB( LDAB, * ), AFB( LDAFB, * ), B( LDB, * ), BERR( *
23                          ), C( * ), FERR( * ), R( * ), WORK( * ), X( LDX, * )
24

PURPOSE

26       SGBSVX uses the LU factorization to compute the solution to a real sys‐
27       tem of linear equations A * X = B, A**T * X = B, or A**H * X = B, where
28       A  is  a band matrix of order N with KL subdiagonals and KU superdiago‐
29       nals, and X and B are N-by-NRHS matrices.
30       Error bounds on the solution and a condition  estimate  are  also  pro‐
31       vided.
32

DESCRIPTION

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

ARGUMENTS

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