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