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

◆ zpbtrs()

subroutine zpbtrs ( character uplo,
integer n,
integer kd,
integer nrhs,
complex*16, dimension( ldab, * ) ab,
integer ldab,
complex*16, dimension( ldb, * ) b,
integer ldb,
integer info )

ZPBTRS

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

Purpose:
!>
!> ZPBTRS solves a system of linear equations A*X = B with a Hermitian
!> positive definite band matrix A using the Cholesky factorization
!> A = U**H *U or A = L*L**H computed by ZPBTRF.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  Upper triangular factor stored in AB;
!>          = 'L':  Lower triangular factor stored in AB.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]KD
!>          KD is INTEGER
!>          The number of superdiagonals of the matrix A if UPLO = 'U',
!>          or the number of subdiagonals if UPLO = 'L'.  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 COMPLEX*16 array, dimension (LDAB,N)
!>          The triangular factor U or L from the Cholesky factorization
!>          A = U**H *U or A = L*L**H of the band matrix A, stored in the
!>          first KD+1 rows of the array.  The j-th column of U or L is
!>          stored in the j-th column of the array AB as follows:
!>          if UPLO ='U', AB(kd+1+i-j,j) = U(i,j) for max(1,j-kd)<=i<=j;
!>          if UPLO ='L', AB(1+i-j,j)    = L(i,j) for j<=i<=min(n,j+kd).
!> 
[in]LDAB
!>          LDAB is INTEGER
!>          The leading dimension of the array AB.  LDAB >= KD+1.
!> 
[in,out]B
!>          B is COMPLEX*16 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 118 of file zpbtrs.f.

119*
120* -- LAPACK computational routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 CHARACTER UPLO
126 INTEGER INFO, KD, LDAB, LDB, N, NRHS
127* ..
128* .. Array Arguments ..
129 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
130* ..
131*
132* =====================================================================
133*
134* .. Local Scalars ..
135 LOGICAL UPPER
136 INTEGER J
137* ..
138* .. External Functions ..
139 LOGICAL LSAME
140 EXTERNAL lsame
141* ..
142* .. External Subroutines ..
143 EXTERNAL xerbla, ztbsv
144* ..
145* .. Intrinsic Functions ..
146 INTRINSIC max
147* ..
148* .. Executable Statements ..
149*
150* Test the input parameters.
151*
152 info = 0
153 upper = lsame( uplo, 'U' )
154 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
155 info = -1
156 ELSE IF( n.LT.0 ) THEN
157 info = -2
158 ELSE IF( kd.LT.0 ) THEN
159 info = -3
160 ELSE IF( nrhs.LT.0 ) THEN
161 info = -4
162 ELSE IF( ldab.LT.kd+1 ) THEN
163 info = -6
164 ELSE IF( ldb.LT.max( 1, n ) ) THEN
165 info = -8
166 END IF
167 IF( info.NE.0 ) THEN
168 CALL xerbla( 'ZPBTRS', -info )
169 RETURN
170 END IF
171*
172* Quick return if possible
173*
174 IF( n.EQ.0 .OR. nrhs.EQ.0 )
175 $ RETURN
176*
177 IF( upper ) THEN
178*
179* Solve A*X = B where A = U**H *U.
180*
181 DO 10 j = 1, nrhs
182*
183* Solve U**H *X = B, overwriting B with X.
184*
185 CALL ztbsv( 'Upper', 'Conjugate transpose', 'Non-unit',
186 $ n,
187 $ kd, ab, ldab, b( 1, j ), 1 )
188*
189* Solve U*X = B, overwriting B with X.
190*
191 CALL ztbsv( 'Upper', 'No transpose', 'Non-unit', n, kd,
192 $ ab,
193 $ ldab, b( 1, j ), 1 )
194 10 CONTINUE
195 ELSE
196*
197* Solve A*X = B where A = L*L**H.
198*
199 DO 20 j = 1, nrhs
200*
201* Solve L*X = B, overwriting B with X.
202*
203 CALL ztbsv( 'Lower', 'No transpose', 'Non-unit', n, kd,
204 $ ab,
205 $ ldab, b( 1, j ), 1 )
206*
207* Solve L**H *X = B, overwriting B with X.
208*
209 CALL ztbsv( 'Lower', 'Conjugate transpose', 'Non-unit',
210 $ n,
211 $ kd, ab, ldab, b( 1, j ), 1 )
212 20 CONTINUE
213 END IF
214*
215 RETURN
216*
217* End of ZPBTRS
218*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine ztbsv(uplo, trans, diag, n, k, a, lda, x, incx)
ZTBSV
Definition ztbsv.f:189
Here is the call graph for this function:
Here is the caller graph for this function: