LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
spbtrs.f
Go to the documentation of this file.
1*> \brief \b SPBTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SPBTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spbtrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spbtrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spbtrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SPBTRS( UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, KD, LDAB, LDB, N, NRHS
24* ..
25* .. Array Arguments ..
26* REAL AB( LDAB, * ), B( LDB, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> SPBTRS solves a system of linear equations A*X = B with a symmetric
36*> positive definite band matrix A using the Cholesky factorization
37*> A = U**T*U or A = L*L**T computed by SPBTRF.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] UPLO
44*> \verbatim
45*> UPLO is CHARACTER*1
46*> = 'U': Upper triangular factor stored in AB;
47*> = 'L': Lower triangular factor stored in AB.
48*> \endverbatim
49*>
50*> \param[in] N
51*> \verbatim
52*> N is INTEGER
53*> The order of the matrix A. N >= 0.
54*> \endverbatim
55*>
56*> \param[in] KD
57*> \verbatim
58*> KD is INTEGER
59*> The number of superdiagonals of the matrix A if UPLO = 'U',
60*> or the number of subdiagonals if UPLO = 'L'. KD >= 0.
61*> \endverbatim
62*>
63*> \param[in] NRHS
64*> \verbatim
65*> NRHS is INTEGER
66*> The number of right hand sides, i.e., the number of columns
67*> of the matrix B. NRHS >= 0.
68*> \endverbatim
69*>
70*> \param[in] AB
71*> \verbatim
72*> AB is REAL array, dimension (LDAB,N)
73*> The triangular factor U or L from the Cholesky factorization
74*> A = U**T*U or A = L*L**T of the band matrix A, stored in the
75*> first KD+1 rows of the array. The j-th column of U or L is
76*> stored in the j-th column of the array AB as follows:
77*> if UPLO ='U', AB(kd+1+i-j,j) = U(i,j) for max(1,j-kd)<=i<=j;
78*> if UPLO ='L', AB(1+i-j,j) = L(i,j) for j<=i<=min(n,j+kd).
79*> \endverbatim
80*>
81*> \param[in] LDAB
82*> \verbatim
83*> LDAB is INTEGER
84*> The leading dimension of the array AB. LDAB >= KD+1.
85*> \endverbatim
86*>
87*> \param[in,out] B
88*> \verbatim
89*> B is REAL array, dimension (LDB,NRHS)
90*> On entry, the right hand side matrix B.
91*> On exit, the solution matrix X.
92*> \endverbatim
93*>
94*> \param[in] LDB
95*> \verbatim
96*> LDB is INTEGER
97*> The leading dimension of the array B. LDB >= max(1,N).
98*> \endverbatim
99*>
100*> \param[out] INFO
101*> \verbatim
102*> INFO is INTEGER
103*> = 0: successful exit
104*> < 0: if INFO = -i, the i-th argument had an illegal value
105*> \endverbatim
106*
107* Authors:
108* ========
109*
110*> \author Univ. of Tennessee
111*> \author Univ. of California Berkeley
112*> \author Univ. of Colorado Denver
113*> \author NAG Ltd.
114*
115*> \ingroup pbtrs
116*
117* =====================================================================
118 SUBROUTINE spbtrs( UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO )
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 REAL 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 stbsv, xerbla
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( 'SPBTRS', -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**T *U.
180*
181 DO 10 j = 1, nrhs
182*
183* Solve U**T *X = B, overwriting B with X.
184*
185 CALL stbsv( 'Upper', 'Transpose', 'Non-unit', n, kd, ab,
186 $ ldab, b( 1, j ), 1 )
187*
188* Solve U*X = B, overwriting B with X.
189*
190 CALL stbsv( 'Upper', 'No transpose', 'Non-unit', n, kd,
191 $ ab,
192 $ ldab, b( 1, j ), 1 )
193 10 CONTINUE
194 ELSE
195*
196* Solve A*X = B where A = L*L**T.
197*
198 DO 20 j = 1, nrhs
199*
200* Solve L*X = B, overwriting B with X.
201*
202 CALL stbsv( 'Lower', 'No transpose', 'Non-unit', n, kd,
203 $ ab,
204 $ ldab, b( 1, j ), 1 )
205*
206* Solve L**T *X = B, overwriting B with X.
207*
208 CALL stbsv( 'Lower', 'Transpose', 'Non-unit', n, kd, ab,
209 $ ldab, b( 1, j ), 1 )
210 20 CONTINUE
211 END IF
212*
213 RETURN
214*
215* End of SPBTRS
216*
217 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine spbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
SPBTRS
Definition spbtrs.f:119
subroutine stbsv(uplo, trans, diag, n, k, a, lda, x, incx)
STBSV
Definition stbsv.f:189