LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cgbsv.f
Go to the documentation of this file.
1 *> \brief <b> CGBSV computes the solution to system of linear equations A * X = B for GB matrices</b> (simple driver)
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CGBSV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgbsv.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgbsv.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgbsv.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CGBSV( N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER INFO, KL, KU, LDAB, LDB, N, NRHS
25 * ..
26 * .. Array Arguments ..
27 * INTEGER IPIV( * )
28 * COMPLEX AB( LDAB, * ), B( LDB, * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> CGBSV computes the solution to a complex system of linear equations
38 *> A * X = B, where A is a band matrix of order N with KL subdiagonals
39 *> and KU superdiagonals, and X and B are N-by-NRHS matrices.
40 *>
41 *> The LU decomposition with partial pivoting and row interchanges is
42 *> used to factor A as A = L * U, where L is a product of permutation
43 *> and unit lower triangular matrices with KL subdiagonals, and U is
44 *> upper triangular with KL+KU superdiagonals. The factored form of A
45 *> is then used to solve the system of equations A * X = B.
46 *> \endverbatim
47 *
48 * Arguments:
49 * ==========
50 *
51 *> \param[in] N
52 *> \verbatim
53 *> N is INTEGER
54 *> The number of linear equations, i.e., the order of the
55 *> matrix A. N >= 0.
56 *> \endverbatim
57 *>
58 *> \param[in] KL
59 *> \verbatim
60 *> KL is INTEGER
61 *> The number of subdiagonals within the band of A. KL >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in] KU
65 *> \verbatim
66 *> KU is INTEGER
67 *> The number of superdiagonals within the band of A. KU >= 0.
68 *> \endverbatim
69 *>
70 *> \param[in] NRHS
71 *> \verbatim
72 *> NRHS is INTEGER
73 *> The number of right hand sides, i.e., the number of columns
74 *> of the matrix B. NRHS >= 0.
75 *> \endverbatim
76 *>
77 *> \param[in,out] AB
78 *> \verbatim
79 *> AB is COMPLEX array, dimension (LDAB,N)
80 *> On entry, the matrix A in band storage, in rows KL+1 to
81 *> 2*KL+KU+1; rows 1 to KL of the array need not be set.
82 *> The j-th column of A is stored in the j-th column of the
83 *> array AB as follows:
84 *> AB(KL+KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+KL)
85 *> On exit, details of the factorization: U is stored as an
86 *> upper triangular band matrix with KL+KU superdiagonals in
87 *> rows 1 to KL+KU+1, and the multipliers used during the
88 *> factorization are stored in rows KL+KU+2 to 2*KL+KU+1.
89 *> See below for further details.
90 *> \endverbatim
91 *>
92 *> \param[in] LDAB
93 *> \verbatim
94 *> LDAB is INTEGER
95 *> The leading dimension of the array AB. LDAB >= 2*KL+KU+1.
96 *> \endverbatim
97 *>
98 *> \param[out] IPIV
99 *> \verbatim
100 *> IPIV is INTEGER array, dimension (N)
101 *> The pivot indices that define the permutation matrix P;
102 *> row i of the matrix was interchanged with row IPIV(i).
103 *> \endverbatim
104 *>
105 *> \param[in,out] B
106 *> \verbatim
107 *> B is COMPLEX array, dimension (LDB,NRHS)
108 *> On entry, the N-by-NRHS right hand side matrix B.
109 *> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
110 *> \endverbatim
111 *>
112 *> \param[in] LDB
113 *> \verbatim
114 *> LDB is INTEGER
115 *> The leading dimension of the array B. LDB >= max(1,N).
116 *> \endverbatim
117 *>
118 *> \param[out] INFO
119 *> \verbatim
120 *> INFO is INTEGER
121 *> = 0: successful exit
122 *> < 0: if INFO = -i, the i-th argument had an illegal value
123 *> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
124 *> has been completed, but the factor U is exactly
125 *> singular, and the solution has not been computed.
126 *> \endverbatim
127 *
128 * Authors:
129 * ========
130 *
131 *> \author Univ. of Tennessee
132 *> \author Univ. of California Berkeley
133 *> \author Univ. of Colorado Denver
134 *> \author NAG Ltd.
135 *
136 *> \date November 2011
137 *
138 *> \ingroup complexGBsolve
139 *
140 *> \par Further Details:
141 * =====================
142 *>
143 *> \verbatim
144 *>
145 *> The band storage scheme is illustrated by the following example, when
146 *> M = N = 6, KL = 2, KU = 1:
147 *>
148 *> On entry: On exit:
149 *>
150 *> * * * + + + * * * u14 u25 u36
151 *> * * + + + + * * u13 u24 u35 u46
152 *> * a12 a23 a34 a45 a56 * u12 u23 u34 u45 u56
153 *> a11 a22 a33 a44 a55 a66 u11 u22 u33 u44 u55 u66
154 *> a21 a32 a43 a54 a65 * m21 m32 m43 m54 m65 *
155 *> a31 a42 a53 a64 * * m31 m42 m53 m64 * *
156 *>
157 *> Array elements marked * are not used by the routine; elements marked
158 *> + need not be set on entry, but are required by the routine to store
159 *> elements of U because of fill-in resulting from the row interchanges.
160 *> \endverbatim
161 *>
162 * =====================================================================
163  SUBROUTINE cgbsv( N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO )
164 *
165 * -- LAPACK driver routine (version 3.4.0) --
166 * -- LAPACK is a software package provided by Univ. of Tennessee, --
167 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168 * November 2011
169 *
170 * .. Scalar Arguments ..
171  INTEGER INFO, KL, KU, LDAB, LDB, N, NRHS
172 * ..
173 * .. Array Arguments ..
174  INTEGER IPIV( * )
175  COMPLEX AB( ldab, * ), B( ldb, * )
176 * ..
177 *
178 * =====================================================================
179 *
180 * .. External Subroutines ..
181  EXTERNAL cgbtrf, cgbtrs, xerbla
182 * ..
183 * .. Intrinsic Functions ..
184  INTRINSIC max
185 * ..
186 * .. Executable Statements ..
187 *
188 * Test the input parameters.
189 *
190  info = 0
191  IF( n.LT.0 ) THEN
192  info = -1
193  ELSE IF( kl.LT.0 ) THEN
194  info = -2
195  ELSE IF( ku.LT.0 ) THEN
196  info = -3
197  ELSE IF( nrhs.LT.0 ) THEN
198  info = -4
199  ELSE IF( ldab.LT.2*kl+ku+1 ) THEN
200  info = -6
201  ELSE IF( ldb.LT.max( n, 1 ) ) THEN
202  info = -9
203  END IF
204  IF( info.NE.0 ) THEN
205  CALL xerbla( 'CGBSV ', -info )
206  RETURN
207  END IF
208 *
209 * Compute the LU factorization of the band matrix A.
210 *
211  CALL cgbtrf( n, n, kl, ku, ab, ldab, ipiv, info )
212  IF( info.EQ.0 ) THEN
213 *
214 * Solve the system A*X = B, overwriting B with X.
215 *
216  CALL cgbtrs( 'No transpose', n, kl, ku, nrhs, ab, ldab, ipiv,
217  $ b, ldb, info )
218  END IF
219  RETURN
220 *
221 * End of CGBSV
222 *
223  END
subroutine cgbtrf(M, N, KL, KU, AB, LDAB, IPIV, INFO)
CGBTRF
Definition: cgbtrf.f:146
subroutine cgbsv(N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
CGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver) ...
Definition: cgbsv.f:164
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cgbtrs(TRANS, N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
CGBTRS
Definition: cgbtrs.f:140