LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zgbtrs.f
Go to the documentation of this file.
1*> \brief \b ZGBTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZGBTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgbtrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgbtrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbtrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZGBTRS( TRANS, N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB,
20* INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER TRANS
24* INTEGER INFO, KL, KU, LDAB, LDB, N, NRHS
25* ..
26* .. Array Arguments ..
27* INTEGER IPIV( * )
28* COMPLEX*16 AB( LDAB, * ), B( LDB, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZGBTRS solves a system of linear equations
38*> A * X = B, A**T * X = B, or A**H * X = B
39*> with a general band matrix A using the LU factorization computed
40*> by ZGBTRF.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] TRANS
47*> \verbatim
48*> TRANS is CHARACTER*1
49*> Specifies the form of the system of equations.
50*> = 'N': A * X = B (No transpose)
51*> = 'T': A**T * X = B (Transpose)
52*> = 'C': A**H * X = B (Conjugate transpose)
53*> \endverbatim
54*>
55*> \param[in] N
56*> \verbatim
57*> N is INTEGER
58*> The order of the matrix A. N >= 0.
59*> \endverbatim
60*>
61*> \param[in] KL
62*> \verbatim
63*> KL is INTEGER
64*> The number of subdiagonals within the band of A. KL >= 0.
65*> \endverbatim
66*>
67*> \param[in] KU
68*> \verbatim
69*> KU is INTEGER
70*> The number of superdiagonals within the band of A. KU >= 0.
71*> \endverbatim
72*>
73*> \param[in] NRHS
74*> \verbatim
75*> NRHS is INTEGER
76*> The number of right hand sides, i.e., the number of columns
77*> of the matrix B. NRHS >= 0.
78*> \endverbatim
79*>
80*> \param[in] AB
81*> \verbatim
82*> AB is COMPLEX*16 array, dimension (LDAB,N)
83*> Details of the LU factorization of the band matrix A, as
84*> computed by ZGBTRF. U is stored as an upper triangular band
85*> matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and
86*> the multipliers used during the factorization are stored in
87*> rows KL+KU+2 to 2*KL+KU+1.
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[in] IPIV
97*> \verbatim
98*> IPIV is INTEGER array, dimension (N)
99*> The pivot indices; for 1 <= i <= N, row i of the matrix was
100*> interchanged with row IPIV(i).
101*> \endverbatim
102*>
103*> \param[in,out] B
104*> \verbatim
105*> B is COMPLEX*16 array, dimension (LDB,NRHS)
106*> On entry, the right hand side matrix B.
107*> On exit, the 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*> \endverbatim
122*
123* Authors:
124* ========
125*
126*> \author Univ. of Tennessee
127*> \author Univ. of California Berkeley
128*> \author Univ. of Colorado Denver
129*> \author NAG Ltd.
130*
131*> \ingroup gbtrs
132*
133* =====================================================================
134 SUBROUTINE zgbtrs( TRANS, N, KL, KU, NRHS, AB, LDAB, IPIV, B,
135 $ LDB,
136 $ INFO )
137*
138* -- LAPACK computational routine --
139* -- LAPACK is a software package provided by Univ. of Tennessee, --
140* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
141*
142* .. Scalar Arguments ..
143 CHARACTER TRANS
144 INTEGER INFO, KL, KU, LDAB, LDB, N, NRHS
145* ..
146* .. Array Arguments ..
147 INTEGER IPIV( * )
148 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
149* ..
150*
151* =====================================================================
152*
153* .. Parameters ..
154 COMPLEX*16 ONE
155 PARAMETER ( ONE = ( 1.0d+0, 0.0d+0 ) )
156* ..
157* .. Local Scalars ..
158 LOGICAL LNOTI, NOTRAN
159 INTEGER I, J, KD, L, LM
160* ..
161* .. External Functions ..
162 LOGICAL LSAME
163 EXTERNAL LSAME
164* ..
165* .. External Subroutines ..
166 EXTERNAL xerbla, zgemv, zgeru, zlacgv, zswap,
167 $ ztbsv
168* ..
169* .. Intrinsic Functions ..
170 INTRINSIC max, min
171* ..
172* .. Executable Statements ..
173*
174* Test the input parameters.
175*
176 info = 0
177 notran = lsame( trans, 'N' )
178 IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) .AND. .NOT.
179 $ lsame( trans, 'C' ) ) THEN
180 info = -1
181 ELSE IF( n.LT.0 ) THEN
182 info = -2
183 ELSE IF( kl.LT.0 ) THEN
184 info = -3
185 ELSE IF( ku.LT.0 ) THEN
186 info = -4
187 ELSE IF( nrhs.LT.0 ) THEN
188 info = -5
189 ELSE IF( ldab.LT.( 2*kl+ku+1 ) ) THEN
190 info = -7
191 ELSE IF( ldb.LT.max( 1, n ) ) THEN
192 info = -10
193 END IF
194 IF( info.NE.0 ) THEN
195 CALL xerbla( 'ZGBTRS', -info )
196 RETURN
197 END IF
198*
199* Quick return if possible
200*
201 IF( n.EQ.0 .OR. nrhs.EQ.0 )
202 $ RETURN
203*
204 kd = ku + kl + 1
205 lnoti = kl.GT.0
206*
207 IF( notran ) THEN
208*
209* Solve A*X = B.
210*
211* Solve L*X = B, overwriting B with X.
212*
213* L is represented as a product of permutations and unit lower
214* triangular matrices L = P(1) * L(1) * ... * P(n-1) * L(n-1),
215* where each transformation L(i) is a rank-one modification of
216* the identity matrix.
217*
218 IF( lnoti ) THEN
219 DO 10 j = 1, n - 1
220 lm = min( kl, n-j )
221 l = ipiv( j )
222 IF( l.NE.j )
223 $ CALL zswap( nrhs, b( l, 1 ), ldb, b( j, 1 ), ldb )
224 CALL zgeru( lm, nrhs, -one, ab( kd+1, j ), 1, b( j,
225 $ 1 ),
226 $ ldb, b( j+1, 1 ), ldb )
227 10 CONTINUE
228 END IF
229*
230 DO 20 i = 1, nrhs
231*
232* Solve U*X = B, overwriting B with X.
233*
234 CALL ztbsv( 'Upper', 'No transpose', 'Non-unit', n,
235 $ kl+ku,
236 $ ab, ldab, b( 1, i ), 1 )
237 20 CONTINUE
238*
239 ELSE IF( lsame( trans, 'T' ) ) THEN
240*
241* Solve A**T * X = B.
242*
243 DO 30 i = 1, nrhs
244*
245* Solve U**T * X = B, overwriting B with X.
246*
247 CALL ztbsv( 'Upper', 'Transpose', 'Non-unit', n, kl+ku,
248 $ ab,
249 $ ldab, b( 1, i ), 1 )
250 30 CONTINUE
251*
252* Solve L**T * X = B, overwriting B with X.
253*
254 IF( lnoti ) THEN
255 DO 40 j = n - 1, 1, -1
256 lm = min( kl, n-j )
257 CALL zgemv( 'Transpose', lm, nrhs, -one, b( j+1, 1 ),
258 $ ldb, ab( kd+1, j ), 1, one, b( j, 1 ), ldb )
259 l = ipiv( j )
260 IF( l.NE.j )
261 $ CALL zswap( nrhs, b( l, 1 ), ldb, b( j, 1 ), ldb )
262 40 CONTINUE
263 END IF
264*
265 ELSE
266*
267* Solve A**H * X = B.
268*
269 DO 50 i = 1, nrhs
270*
271* Solve U**H * X = B, overwriting B with X.
272*
273 CALL ztbsv( 'Upper', 'Conjugate transpose', 'Non-unit',
274 $ n,
275 $ kl+ku, ab, ldab, b( 1, i ), 1 )
276 50 CONTINUE
277*
278* Solve L**H * X = B, overwriting B with X.
279*
280 IF( lnoti ) THEN
281 DO 60 j = n - 1, 1, -1
282 lm = min( kl, n-j )
283 CALL zlacgv( nrhs, b( j, 1 ), ldb )
284 CALL zgemv( 'Conjugate transpose', lm, nrhs, -one,
285 $ b( j+1, 1 ), ldb, ab( kd+1, j ), 1, one,
286 $ b( j, 1 ), ldb )
287 CALL zlacgv( nrhs, b( j, 1 ), ldb )
288 l = ipiv( j )
289 IF( l.NE.j )
290 $ CALL zswap( nrhs, b( l, 1 ), ldb, b( j, 1 ), ldb )
291 60 CONTINUE
292 END IF
293 END IF
294 RETURN
295*
296* End of ZGBTRS
297*
298 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgbtrs(trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)
ZGBTRS
Definition zgbtrs.f:137
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zgeru(m, n, alpha, x, incx, y, incy, a, lda)
ZGERU
Definition zgeru.f:130
subroutine zlacgv(n, x, incx)
ZLACGV conjugates a complex vector.
Definition zlacgv.f:72
subroutine zswap(n, zx, incx, zy, incy)
ZSWAP
Definition zswap.f:81
subroutine ztbsv(uplo, trans, diag, n, k, a, lda, x, incx)
ZTBSV
Definition ztbsv.f:189