LAPACK 3.12.0
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*> \htmlonly
9*> Download ZTBTRS + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztbtrs.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztbtrs.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztbtrs.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE ZTBTRS( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB, B,
22* LDB, INFO )
23*
24* .. Scalar Arguments ..
25* CHARACTER DIAG, TRANS, UPLO
26* INTEGER INFO, KD, LDAB, LDB, N, NRHS
27* ..
28* .. Array Arguments ..
29* COMPLEX*16 AB( LDAB, * ), B( LDB, * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> ZTBTRS solves a triangular system of the form
39*>
40*> A * X = B, A**T * X = B, or A**H * X = B,
41*>
42*> where A is a triangular band matrix of order N, and B is an
43*> N-by-NRHS matrix. A check is made to verify that A is nonsingular.
44*> \endverbatim
45*
46* Arguments:
47* ==========
48*
49*> \param[in] UPLO
50*> \verbatim
51*> UPLO is CHARACTER*1
52*> = 'U': A is upper triangular;
53*> = 'L': A is lower triangular.
54*> \endverbatim
55*>
56*> \param[in] TRANS
57*> \verbatim
58*> TRANS is CHARACTER*1
59*> Specifies the form of the system of equations:
60*> = 'N': A * X = B (No transpose)
61*> = 'T': A**T * X = B (Transpose)
62*> = 'C': A**H * X = B (Conjugate transpose)
63*> \endverbatim
64*>
65*> \param[in] DIAG
66*> \verbatim
67*> DIAG is CHARACTER*1
68*> = 'N': A is non-unit triangular;
69*> = 'U': A is unit triangular.
70*> \endverbatim
71*>
72*> \param[in] N
73*> \verbatim
74*> N is INTEGER
75*> The order of the matrix A. N >= 0.
76*> \endverbatim
77*>
78*> \param[in] KD
79*> \verbatim
80*> KD is INTEGER
81*> The number of superdiagonals or subdiagonals of the
82*> triangular band matrix A. KD >= 0.
83*> \endverbatim
84*>
85*> \param[in] NRHS
86*> \verbatim
87*> NRHS is INTEGER
88*> The number of right hand sides, i.e., the number of columns
89*> of the matrix B. NRHS >= 0.
90*> \endverbatim
91*>
92*> \param[in] AB
93*> \verbatim
94*> AB is COMPLEX*16 array, dimension (LDAB,N)
95*> The upper or lower triangular band matrix A, stored in the
96*> first kd+1 rows of AB. The j-th column of A is stored
97*> in the j-th column of the array AB as follows:
98*> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
99*> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
100*> If DIAG = 'U', the diagonal elements of A are not referenced
101*> and are assumed to be 1.
102*> \endverbatim
103*>
104*> \param[in] LDAB
105*> \verbatim
106*> LDAB is INTEGER
107*> The leading dimension of the array AB. LDAB >= KD+1.
108*> \endverbatim
109*>
110*> \param[in,out] B
111*> \verbatim
112*> B is COMPLEX*16 array, dimension (LDB,NRHS)
113*> On entry, the right hand side matrix B.
114*> On exit, if INFO = 0, the solution matrix X.
115*> \endverbatim
116*>
117*> \param[in] LDB
118*> \verbatim
119*> LDB is INTEGER
120*> The leading dimension of the array B. LDB >= max(1,N).
121*> \endverbatim
122*>
123*> \param[out] INFO
124*> \verbatim
125*> INFO is INTEGER
126*> = 0: successful exit
127*> < 0: if INFO = -i, the i-th argument had an illegal value
128*> > 0: if INFO = i, the i-th diagonal element of A is zero,
129*> indicating that the matrix is singular and the
130*> solutions X have not been computed.
131*> \endverbatim
132*
133* Authors:
134* ========
135*
136*> \author Univ. of Tennessee
137*> \author Univ. of California Berkeley
138*> \author Univ. of Colorado Denver
139*> \author NAG Ltd.
140*
141*> \ingroup tbtrs
142*
143* =====================================================================
144 SUBROUTINE ztbtrs( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB, B,
145 $ LDB, INFO )
146*
147* -- LAPACK computational routine --
148* -- LAPACK is a software package provided by Univ. of Tennessee, --
149* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
150*
151* .. Scalar Arguments ..
152 CHARACTER DIAG, TRANS, UPLO
153 INTEGER INFO, KD, LDAB, LDB, N, NRHS
154* ..
155* .. Array Arguments ..
156 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
157* ..
158*
159* =====================================================================
160*
161* .. Parameters ..
162 COMPLEX*16 ZERO
163 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
164* ..
165* .. Local Scalars ..
166 LOGICAL NOUNIT, UPPER
167 INTEGER J
168* ..
169* .. External Functions ..
170 LOGICAL LSAME
171 EXTERNAL lsame
172* ..
173* .. External Subroutines ..
174 EXTERNAL xerbla, ztbsv
175* ..
176* .. Intrinsic Functions ..
177 INTRINSIC max
178* ..
179* .. Executable Statements ..
180*
181* Test the input parameters.
182*
183 info = 0
184 nounit = lsame( diag, 'N' )
185 upper = lsame( uplo, 'U' )
186 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
187 info = -1
188 ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.
189 $ lsame( trans, 'T' ) .AND. .NOT.lsame( trans, 'C' ) ) THEN
190 info = -2
191 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
192 info = -3
193 ELSE IF( n.LT.0 ) THEN
194 info = -4
195 ELSE IF( kd.LT.0 ) THEN
196 info = -5
197 ELSE IF( nrhs.LT.0 ) THEN
198 info = -6
199 ELSE IF( ldab.LT.kd+1 ) THEN
200 info = -8
201 ELSE IF( ldb.LT.max( 1, n ) ) THEN
202 info = -10
203 END IF
204 IF( info.NE.0 ) THEN
205 CALL xerbla( 'ZTBTRS', -info )
206 RETURN
207 END IF
208*
209* Quick return if possible
210*
211 IF( n.EQ.0 )
212 $ RETURN
213*
214* Check for singularity.
215*
216 IF( nounit ) THEN
217 IF( upper ) THEN
218 DO 10 info = 1, n
219 IF( ab( kd+1, info ).EQ.zero )
220 $ RETURN
221 10 CONTINUE
222 ELSE
223 DO 20 info = 1, n
224 IF( ab( 1, info ).EQ.zero )
225 $ RETURN
226 20 CONTINUE
227 END IF
228 END IF
229 info = 0
230*
231* Solve A * X = B, A**T * X = B, or A**H * X = B.
232*
233 DO 30 j = 1, nrhs
234 CALL ztbsv( uplo, trans, diag, n, kd, ab, ldab, b( 1, j ), 1 )
235 30 CONTINUE
236*
237 RETURN
238*
239* End of ZTBTRS
240*
241 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:146