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

◆ dtbtrs()

subroutine dtbtrs ( character uplo,
character trans,
character diag,
integer n,
integer kd,
integer nrhs,
double precision, dimension( ldab, * ) ab,
integer ldab,
double precision, dimension( ldb, * ) b,
integer ldb,
integer info )

DTBTRS

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

Purpose:
!>
!> DTBTRS solves a triangular system of the form
!>
!>    A * X = B  or  A**T * X = B,
!>
!> where A is a triangular band matrix of order N, and B is an N-by-NRHS matrix.
!>
!> This subroutine verifies that A is nonsingular, but callers should note that only exact
!> singularity is detected. It is conceivable for one or more diagonal elements of A to be
!> subnormally tiny numbers without this subroutine signalling an error.
!>
!> If a possible loss of numerical precision due to near-singular matrices is a concern, the
!> caller should verify that A is nonsingular within some tolerance before calling this subroutine.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  A is upper triangular;
!>          = 'L':  A is lower triangular.
!> 
[in]TRANS
!>          TRANS is CHARACTER*1
!>          Specifies the form the system of equations:
!>          = 'N':  A * X = B  (No transpose)
!>          = 'T':  A**T * X = B  (Transpose)
!>          = 'C':  A**H * X = B  (Conjugate transpose = Transpose)
!> 
[in]DIAG
!>          DIAG is CHARACTER*1
!>          = 'N':  A is non-unit triangular;
!>          = 'U':  A is unit triangular.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]KD
!>          KD is INTEGER
!>          The number of superdiagonals or subdiagonals of the
!>          triangular band matrix A.  KD >= 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 DOUBLE PRECISION array, dimension (LDAB,N)
!>          The upper or lower triangular band matrix A, stored in the
!>          first kd+1 rows of AB.  The j-th column of A is stored
!>          in the j-th column of the array AB as follows:
!>          if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
!>          if UPLO = 'L', AB(1+i-j,j)    = A(i,j) for j<=i<=min(n,j+kd).
!>          If DIAG = 'U', the diagonal elements of A are not referenced
!>          and are assumed to be 1.
!> 
[in]LDAB
!>          LDAB is INTEGER
!>          The leading dimension of the array AB.  LDAB >= KD+1.
!> 
[in,out]B
!>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
!>          On entry, the right hand side matrix B.
!>          On exit, if INFO = 0, 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
!>          > 0:  if INFO = i, the i-th diagonal element of A is exactly zero,
!>                indicating that the matrix is singular and the
!>                solutions X have not been computed.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 148 of file dtbtrs.f.

150*
151* -- LAPACK computational routine --
152* -- LAPACK is a software package provided by Univ. of Tennessee, --
153* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
154*
155* .. Scalar Arguments ..
156 CHARACTER DIAG, TRANS, UPLO
157 INTEGER INFO, KD, LDAB, LDB, N, NRHS
158* ..
159* .. Array Arguments ..
160 DOUBLE PRECISION AB( LDAB, * ), B( LDB, * )
161* ..
162*
163* =====================================================================
164*
165* .. Parameters ..
166 DOUBLE PRECISION ZERO
167 parameter( zero = 0.0d+0 )
168* ..
169* .. Local Scalars ..
170 LOGICAL NOUNIT, UPPER
171 INTEGER J
172* ..
173* .. External Functions ..
174 LOGICAL LSAME
175 EXTERNAL lsame
176* ..
177* .. External Subroutines ..
178 EXTERNAL dtbsv, xerbla
179* ..
180* .. Intrinsic Functions ..
181 INTRINSIC max
182* ..
183* .. Executable Statements ..
184*
185* Test the input parameters.
186*
187 info = 0
188 nounit = lsame( diag, 'N' )
189 upper = lsame( uplo, 'U' )
190 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
191 info = -1
192 ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.
193 $ lsame( trans, 'T' ) .AND.
194 $ .NOT.lsame( trans, 'C' ) ) THEN
195 info = -2
196 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
197 info = -3
198 ELSE IF( n.LT.0 ) THEN
199 info = -4
200 ELSE IF( kd.LT.0 ) THEN
201 info = -5
202 ELSE IF( nrhs.LT.0 ) THEN
203 info = -6
204 ELSE IF( ldab.LT.kd+1 ) THEN
205 info = -8
206 ELSE IF( ldb.LT.max( 1, n ) ) THEN
207 info = -10
208 END IF
209 IF( info.NE.0 ) THEN
210 CALL xerbla( 'DTBTRS', -info )
211 RETURN
212 END IF
213*
214* Quick return if possible
215*
216 IF( n.EQ.0 )
217 $ RETURN
218*
219* Check for singularity.
220*
221 IF( nounit ) THEN
222 IF( upper ) THEN
223 DO 10 info = 1, n
224 IF( ab( kd+1, info ).EQ.zero )
225 $ RETURN
226 10 CONTINUE
227 ELSE
228 DO 20 info = 1, n
229 IF( ab( 1, info ).EQ.zero )
230 $ RETURN
231 20 CONTINUE
232 END IF
233 END IF
234 info = 0
235*
236* Solve A * X = B or A**T * X = B.
237*
238 DO 30 j = 1, nrhs
239 CALL dtbsv( uplo, trans, diag, n, kd, ab, ldab, b( 1, j ),
240 $ 1 )
241 30 CONTINUE
242*
243 RETURN
244*
245* End of DTBTRS
246*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dtbsv(uplo, trans, diag, n, k, a, lda, x, incx)
DTBSV
Definition dtbsv.f:189
Here is the call graph for this function:
Here is the caller graph for this function: