LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sgbtrs()

subroutine sgbtrs ( character trans,
integer n,
integer kl,
integer ku,
integer nrhs,
real, dimension( ldab, * ) ab,
integer ldab,
integer, dimension( * ) ipiv,
real, dimension( ldb, * ) b,
integer ldb,
integer info )

SGBTRS

Download SGBTRS + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> SGBTRS solves a system of linear equations
!>    A * X = B  or  A**T * X = B
!> with a general band matrix A using the LU factorization computed
!> by SGBTRF.
!> 
Parameters
[in]TRANS
!>          TRANS is CHARACTER*1
!>          Specifies the form of the system of equations.
!>          = 'N':  A * X = B  (No transpose)
!>          = 'T':  A**T* X = B  (Transpose)
!>          = 'C':  A**T* X = B  (Conjugate transpose = Transpose)
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]KL
!>          KL is INTEGER
!>          The number of subdiagonals within the band of A.  KL >= 0.
!> 
[in]KU
!>          KU is INTEGER
!>          The number of superdiagonals within the band of A.  KU >= 0.
!> 
[in]NRHS
!>          NRHS is INTEGER
!>          The number of right hand sides, i.e., the number of columns
!>          of the matrix B.  NRHS >= 0.
!> 
[in]AB
!>          AB is REAL array, dimension (LDAB,N)
!>          Details of the LU factorization of the band matrix A, as
!>          computed by SGBTRF.  U is stored as an upper triangular band
!>          matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and
!>          the multipliers used during the factorization are stored in
!>          rows KL+KU+2 to 2*KL+KU+1.
!> 
[in]LDAB
!>          LDAB is INTEGER
!>          The leading dimension of the array AB.  LDAB >= 2*KL+KU+1.
!> 
[in]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>          The pivot indices; for 1 <= i <= N, row i of the matrix was
!>          interchanged with row IPIV(i).
!> 
[in,out]B
!>          B is REAL array, dimension (LDB,NRHS)
!>          On entry, the right hand side matrix B.
!>          On exit, the solution matrix X.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= max(1,N).
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0: if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 134 of file sgbtrs.f.

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 REAL AB( LDAB, * ), B( LDB, * )
149* ..
150*
151* =====================================================================
152*
153* .. Parameters ..
154 REAL ONE
155 parameter( one = 1.0e+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 sgemv, sger, sswap, stbsv, xerbla
167* ..
168* .. Intrinsic Functions ..
169 INTRINSIC max, min
170* ..
171* .. Executable Statements ..
172*
173* Test the input parameters.
174*
175 info = 0
176 notran = lsame( trans, 'N' )
177 IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) .AND. .NOT.
178 $ lsame( trans, 'C' ) ) THEN
179 info = -1
180 ELSE IF( n.LT.0 ) THEN
181 info = -2
182 ELSE IF( kl.LT.0 ) THEN
183 info = -3
184 ELSE IF( ku.LT.0 ) THEN
185 info = -4
186 ELSE IF( nrhs.LT.0 ) THEN
187 info = -5
188 ELSE IF( ldab.LT.( 2*kl+ku+1 ) ) THEN
189 info = -7
190 ELSE IF( ldb.LT.max( 1, n ) ) THEN
191 info = -10
192 END IF
193 IF( info.NE.0 ) THEN
194 CALL xerbla( 'SGBTRS', -info )
195 RETURN
196 END IF
197*
198* Quick return if possible
199*
200 IF( n.EQ.0 .OR. nrhs.EQ.0 )
201 $ RETURN
202*
203 kd = ku + kl + 1
204 lnoti = kl.GT.0
205*
206 IF( notran ) THEN
207*
208* Solve A*X = B.
209*
210* Solve L*X = B, overwriting B with X.
211*
212* L is represented as a product of permutations and unit lower
213* triangular matrices L = P(1) * L(1) * ... * P(n-1) * L(n-1),
214* where each transformation L(i) is a rank-one modification of
215* the identity matrix.
216*
217 IF( lnoti ) THEN
218 DO 10 j = 1, n - 1
219 lm = min( kl, n-j )
220 l = ipiv( j )
221 IF( l.NE.j )
222 $ CALL sswap( nrhs, b( l, 1 ), ldb, b( j, 1 ), ldb )
223 CALL sger( lm, nrhs, -one, ab( kd+1, j ), 1, b( j,
224 $ 1 ),
225 $ ldb, b( j+1, 1 ), ldb )
226 10 CONTINUE
227 END IF
228*
229 DO 20 i = 1, nrhs
230*
231* Solve U*X = B, overwriting B with X.
232*
233 CALL stbsv( 'Upper', 'No transpose', 'Non-unit', n,
234 $ kl+ku,
235 $ ab, ldab, b( 1, i ), 1 )
236 20 CONTINUE
237*
238 ELSE
239*
240* Solve A**T*X = B.
241*
242 DO 30 i = 1, nrhs
243*
244* Solve U**T*X = B, overwriting B with X.
245*
246 CALL stbsv( 'Upper', 'Transpose', 'Non-unit', n, kl+ku,
247 $ ab,
248 $ ldab, b( 1, i ), 1 )
249 30 CONTINUE
250*
251* Solve L**T*X = B, overwriting B with X.
252*
253 IF( lnoti ) THEN
254 DO 40 j = n - 1, 1, -1
255 lm = min( kl, n-j )
256 CALL sgemv( 'Transpose', lm, nrhs, -one, b( j+1, 1 ),
257 $ ldb, ab( kd+1, j ), 1, one, b( j, 1 ), ldb )
258 l = ipiv( j )
259 IF( l.NE.j )
260 $ CALL sswap( nrhs, b( l, 1 ), ldb, b( j, 1 ), ldb )
261 40 CONTINUE
262 END IF
263 END IF
264 RETURN
265*
266* End of SGBTRS
267*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
Definition sgemv.f:158
subroutine sger(m, n, alpha, x, incx, y, incy, a, lda)
SGER
Definition sger.f:130
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine sswap(n, sx, incx, sy, incy)
SSWAP
Definition sswap.f:82
subroutine stbsv(uplo, trans, diag, n, k, a, lda, x, incx)
STBSV
Definition stbsv.f:189
Here is the call graph for this function:
Here is the caller graph for this function: