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