3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZTBTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztbtrs.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztbtrs.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztbtrs.f">
21 * SUBROUTINE ZTBTRS( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB, B,
24 * .. Scalar Arguments ..
25 * CHARACTER DIAG, TRANS, UPLO
26 * INTEGER INFO, KD, LDAB, LDB, N, NRHS
28 * .. Array Arguments ..
29 * COMPLEX*16 AB( LDAB, * ), B( LDB, * )
38 *> ZTBTRS solves a triangular system of the form
40 *> A * X = B, A**T * X = B, or A**H * X = B,
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.
51 *> UPLO is CHARACTER*1
52 *> = 'U': A is upper triangular;
53 *> = 'L': A is lower triangular.
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)
67 *> DIAG is CHARACTER*1
68 *> = 'N': A is non-unit triangular;
69 *> = 'U': A is unit triangular.
75 *> The order of the matrix A. N >= 0.
81 *> The number of superdiagonals or subdiagonals of the
82 *> triangular band matrix A. KD >= 0.
88 *> The number of right hand sides, i.e., the number of columns
89 *> of the matrix B. NRHS >= 0.
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.
107 *> The leading dimension of the array AB. LDAB >= KD+1.
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.
120 *> The leading dimension of the array B. LDB >= max(1,N).
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.
136 *> \author Univ. of Tennessee
137 *> \author Univ. of California Berkeley
138 *> \author Univ. of Colorado Denver
141 *> \date November 2011
143 *> \ingroup complex16OTHERcomputational
145 * =====================================================================
146 SUBROUTINE ZTBTRS( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB, B,
149 * -- LAPACK computational routine (version 3.4.0) --
150 * -- LAPACK is a software package provided by Univ. of Tennessee, --
151 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
154 * .. Scalar Arguments ..
155 CHARACTER DIAG, TRANS, UPLO
156 INTEGER INFO, KD, LDAB, LDB, N, NRHS
158 * .. Array Arguments ..
159 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
162 * =====================================================================
166 PARAMETER ( ZERO = ( 0.0D+0, 0.0D+0 ) )
168 * .. Local Scalars ..
169 LOGICAL NOUNIT, UPPER
172 * .. External Functions ..
176 * .. External Subroutines ..
177 EXTERNAL XERBLA, ZTBSV
179 * .. Intrinsic Functions ..
182 * .. Executable Statements ..
184 * Test the input parameters.
187 NOUNIT = LSAME( DIAG, 'N' )
188 UPPER = LSAME( UPLO, 'U' )
189 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
191 ELSE IF( .NOT.LSAME( TRANS, 'N' ) .AND. .NOT.
192 $ LSAME( TRANS, 'T' ) .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
194 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
196 ELSE IF( N.LT.0 ) THEN
198 ELSE IF( KD.LT.0 ) THEN
200 ELSE IF( NRHS.LT.0 ) THEN
202 ELSE IF( LDAB.LT.KD+1 ) THEN
204 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
208 CALL XERBLA( 'ZTBTRS', -INFO )
212 * Quick return if possible
217 * Check for singularity.
222 IF( AB( KD+1, INFO ).EQ.ZERO )
227 IF( AB( 1, INFO ).EQ.ZERO )
234 * Solve A * X = B, A**T * X = B, or A**H * X = B.
237 CALL ZTBSV( UPLO, TRANS, DIAG, N, KD, AB, LDAB, B( 1, J ), 1 )