LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ztbtrs.f
Go to the documentation of this file.
1*> \brief \b ZTBTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZTBTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztbtrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztbtrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztbtrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZTBTRS( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB, B,
20* LDB, INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER DIAG, TRANS, UPLO
24* INTEGER INFO, KD, LDAB, LDB, N, NRHS
25* ..
26* .. Array Arguments ..
27* COMPLEX*16 AB( LDAB, * ), B( LDB, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZTBTRS solves a triangular system of the form
37*>
38*> A * X = B, A**T * X = B, or A**H * X = B,
39*>
40*> where A is a triangular band matrix of order N, and B is an N-by-NRHS matrix.
41*>
42*> This subroutine verifies that A is nonsingular, but callers should note that only exact
43*> singularity is detected. It is conceivable for one or more diagonal elements of A to be
44*> subnormally tiny numbers without this subroutine signalling an error.
45*>
46*> If a possible loss of numerical precision due to near-singular matrices is a concern, the
47*> caller should verify that A is nonsingular within some tolerance before calling this subroutine.
48*> \endverbatim
49*
50* Arguments:
51* ==========
52*
53*> \param[in] UPLO
54*> \verbatim
55*> UPLO is CHARACTER*1
56*> = 'U': A is upper triangular;
57*> = 'L': A is lower triangular.
58*> \endverbatim
59*>
60*> \param[in] TRANS
61*> \verbatim
62*> TRANS is CHARACTER*1
63*> Specifies the form of the system of equations:
64*> = 'N': A * X = B (No transpose)
65*> = 'T': A**T * X = B (Transpose)
66*> = 'C': A**H * X = B (Conjugate transpose)
67*> \endverbatim
68*>
69*> \param[in] DIAG
70*> \verbatim
71*> DIAG is CHARACTER*1
72*> = 'N': A is non-unit triangular;
73*> = 'U': A is unit triangular.
74*> \endverbatim
75*>
76*> \param[in] N
77*> \verbatim
78*> N is INTEGER
79*> The order of the matrix A. N >= 0.
80*> \endverbatim
81*>
82*> \param[in] KD
83*> \verbatim
84*> KD is INTEGER
85*> The number of superdiagonals or subdiagonals of the
86*> triangular band matrix A. KD >= 0.
87*> \endverbatim
88*>
89*> \param[in] NRHS
90*> \verbatim
91*> NRHS is INTEGER
92*> The number of right hand sides, i.e., the number of columns
93*> of the matrix B. NRHS >= 0.
94*> \endverbatim
95*>
96*> \param[in] AB
97*> \verbatim
98*> AB is COMPLEX*16 array, dimension (LDAB,N)
99*> The upper or lower triangular band matrix A, stored in the
100*> first kd+1 rows of AB. The j-th column of A is stored
101*> in the j-th column of the array AB as follows:
102*> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
103*> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
104*> If DIAG = 'U', the diagonal elements of A are not referenced
105*> and are assumed to be 1.
106*> \endverbatim
107*>
108*> \param[in] LDAB
109*> \verbatim
110*> LDAB is INTEGER
111*> The leading dimension of the array AB. LDAB >= KD+1.
112*> \endverbatim
113*>
114*> \param[in,out] B
115*> \verbatim
116*> B is COMPLEX*16 array, dimension (LDB,NRHS)
117*> On entry, the right hand side matrix B.
118*> On exit, if INFO = 0, the solution matrix X.
119*> \endverbatim
120*>
121*> \param[in] LDB
122*> \verbatim
123*> LDB is INTEGER
124*> The leading dimension of the array B. LDB >= max(1,N).
125*> \endverbatim
126*>
127*> \param[out] INFO
128*> \verbatim
129*> INFO is INTEGER
130*> = 0: successful exit
131*> < 0: if INFO = -i, the i-th argument had an illegal value
132*> > 0: if INFO = i, the i-th diagonal element of A is exactly zero,
133*> indicating that the matrix is singular and the
134*> solutions X have not been computed.
135*> \endverbatim
136*
137* Authors:
138* ========
139*
140*> \author Univ. of Tennessee
141*> \author Univ. of California Berkeley
142*> \author Univ. of Colorado Denver
143*> \author NAG Ltd.
144*
145*> \ingroup tbtrs
146*
147* =====================================================================
148 SUBROUTINE ztbtrs( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB, B,
149 $ LDB, INFO )
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 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
161* ..
162*
163* =====================================================================
164*
165* .. Parameters ..
166 COMPLEX*16 ZERO
167 parameter( zero = ( 0.0d+0, 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 xerbla, ztbsv
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( 'ZTBTRS', -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, A**T * X = B, or A**H * X = B.
237*
238 DO 30 j = 1, nrhs
239 CALL ztbsv( uplo, trans, diag, n, kd, ab, ldab, b( 1, j ),
240 $ 1 )
241 30 CONTINUE
242*
243 RETURN
244*
245* End of ZTBTRS
246*
247 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ztbsv(uplo, trans, diag, n, k, a, lda, x, incx)
ZTBSV
Definition ztbsv.f:189
subroutine ztbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)
ZTBTRS
Definition ztbtrs.f:150