LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zpbsv.f
Go to the documentation of this file.
1*> \brief <b> ZPBSV computes the solution to system of linear equations A * X = B for OTHER matrices</b>
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZPBSV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zpbsv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zpbsv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpbsv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZPBSV( 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* COMPLEX*16 AB( LDAB, * ), B( LDB, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZPBSV computes the solution to a complex system of linear equations
36*> A * X = B,
37*> where A is an N-by-N Hermitian positive definite band matrix and X
38*> and B are N-by-NRHS matrices.
39*>
40*> The Cholesky decomposition is used to factor A as
41*> A = U**H * U, if UPLO = 'U', or
42*> A = L * L**H, if UPLO = 'L',
43*> where U is an upper triangular band matrix, and L is a lower
44*> triangular band matrix, with the same number of superdiagonals or
45*> subdiagonals as A. The factored form of A is then used to solve the
46*> system of equations A * X = B.
47*> \endverbatim
48*
49* Arguments:
50* ==========
51*
52*> \param[in] UPLO
53*> \verbatim
54*> UPLO is CHARACTER*1
55*> = 'U': Upper triangle of A is stored;
56*> = 'L': Lower triangle of A is stored.
57*> \endverbatim
58*>
59*> \param[in] N
60*> \verbatim
61*> N is INTEGER
62*> The number of linear equations, i.e., the order of the
63*> matrix A. N >= 0.
64*> \endverbatim
65*>
66*> \param[in] KD
67*> \verbatim
68*> KD is INTEGER
69*> The number of superdiagonals of the matrix A if UPLO = 'U',
70*> or the number of subdiagonals if UPLO = 'L'. KD >= 0.
71*> \endverbatim
72*>
73*> \param[in] NRHS
74*> \verbatim
75*> NRHS is INTEGER
76*> The number of right hand sides, i.e., the number of columns
77*> of the matrix B. NRHS >= 0.
78*> \endverbatim
79*>
80*> \param[in,out] AB
81*> \verbatim
82*> AB is COMPLEX*16 array, dimension (LDAB,N)
83*> On entry, the upper or lower triangle of the Hermitian band
84*> matrix A, stored in the first KD+1 rows of the array. The
85*> j-th column of A is stored in the j-th column of the array AB
86*> as follows:
87*> if UPLO = 'U', AB(KD+1+i-j,j) = A(i,j) for max(1,j-KD)<=i<=j;
88*> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(N,j+KD).
89*> See below for further details.
90*>
91*> On exit, if INFO = 0, the triangular factor U or L from the
92*> Cholesky factorization A = U**H *U or A = L*L**H of the band
93*> matrix A, in the same storage format as A.
94*> \endverbatim
95*>
96*> \param[in] LDAB
97*> \verbatim
98*> LDAB is INTEGER
99*> The leading dimension of the array AB. LDAB >= KD+1.
100*> \endverbatim
101*>
102*> \param[in,out] B
103*> \verbatim
104*> B is COMPLEX*16 array, dimension (LDB,NRHS)
105*> On entry, the N-by-NRHS right hand side matrix B.
106*> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
107*> \endverbatim
108*>
109*> \param[in] LDB
110*> \verbatim
111*> LDB is INTEGER
112*> The leading dimension of the array B. LDB >= max(1,N).
113*> \endverbatim
114*>
115*> \param[out] INFO
116*> \verbatim
117*> INFO is INTEGER
118*> = 0: successful exit
119*> < 0: if INFO = -i, the i-th argument had an illegal value
120*> > 0: if INFO = i, the leading principal minor of order i
121*> of A is not positive, so the factorization could not
122*> be completed, and the solution has not been computed.
123*> \endverbatim
124*
125* Authors:
126* ========
127*
128*> \author Univ. of Tennessee
129*> \author Univ. of California Berkeley
130*> \author Univ. of Colorado Denver
131*> \author NAG Ltd.
132*
133*> \ingroup pbsv
134*
135*> \par Further Details:
136* =====================
137*>
138*> \verbatim
139*>
140*> The band storage scheme is illustrated by the following example, when
141*> N = 6, KD = 2, and UPLO = 'U':
142*>
143*> On entry: On exit:
144*>
145*> * * a13 a24 a35 a46 * * u13 u24 u35 u46
146*> * a12 a23 a34 a45 a56 * u12 u23 u34 u45 u56
147*> a11 a22 a33 a44 a55 a66 u11 u22 u33 u44 u55 u66
148*>
149*> Similarly, if UPLO = 'L' the format of A is as follows:
150*>
151*> On entry: On exit:
152*>
153*> a11 a22 a33 a44 a55 a66 l11 l22 l33 l44 l55 l66
154*> a21 a32 a43 a54 a65 * l21 l32 l43 l54 l65 *
155*> a31 a42 a53 a64 * * l31 l42 l53 l64 * *
156*>
157*> Array elements marked * are not used by the routine.
158*> \endverbatim
159*>
160* =====================================================================
161 SUBROUTINE zpbsv( UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO )
162*
163* -- LAPACK driver routine --
164* -- LAPACK is a software package provided by Univ. of Tennessee, --
165* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
166*
167* .. Scalar Arguments ..
168 CHARACTER UPLO
169 INTEGER INFO, KD, LDAB, LDB, N, NRHS
170* ..
171* .. Array Arguments ..
172 COMPLEX*16 AB( LDAB, * ), B( LDB, * )
173* ..
174*
175* =====================================================================
176*
177* .. External Functions ..
178 LOGICAL LSAME
179 EXTERNAL lsame
180* ..
181* .. External Subroutines ..
182 EXTERNAL xerbla, zpbtrf, zpbtrs
183* ..
184* .. Intrinsic Functions ..
185 INTRINSIC max
186* ..
187* .. Executable Statements ..
188*
189* Test the input parameters.
190*
191 info = 0
192 IF( .NOT.lsame( uplo, 'U' ) .AND.
193 $ .NOT.lsame( uplo, 'L' ) ) THEN
194 info = -1
195 ELSE IF( n.LT.0 ) THEN
196 info = -2
197 ELSE IF( kd.LT.0 ) THEN
198 info = -3
199 ELSE IF( nrhs.LT.0 ) THEN
200 info = -4
201 ELSE IF( ldab.LT.kd+1 ) THEN
202 info = -6
203 ELSE IF( ldb.LT.max( 1, n ) ) THEN
204 info = -8
205 END IF
206 IF( info.NE.0 ) THEN
207 CALL xerbla( 'ZPBSV ', -info )
208 RETURN
209 END IF
210*
211* Compute the Cholesky factorization A = U**H *U or A = L*L**H.
212*
213 CALL zpbtrf( uplo, n, kd, ab, ldab, info )
214 IF( info.EQ.0 ) THEN
215*
216* Solve the system A*X = B, overwriting B with X.
217*
218 CALL zpbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
219*
220 END IF
221 RETURN
222*
223* End of ZPBSV
224*
225 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zpbsv(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
ZPBSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition zpbsv.f:162
subroutine zpbtrf(uplo, n, kd, ab, ldab, info)
ZPBTRF
Definition zpbtrf.f:140
subroutine zpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
ZPBTRS
Definition zpbtrs.f:119