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

◆ dpbsv()

subroutine dpbsv ( character  uplo,
integer  n,
integer  kd,
integer  nrhs,
double precision, dimension( ldab, * )  ab,
integer  ldab,
double precision, dimension( ldb, * )  b,
integer  ldb,
integer  info 
)

DPBSV computes the solution to system of linear equations A * X = B for OTHER matrices

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

Purpose:
 DPBSV computes the solution to a real system of linear equations
    A * X = B,
 where A is an N-by-N symmetric positive definite band matrix and X
 and B are N-by-NRHS matrices.

 The Cholesky decomposition is used to factor A as
    A = U**T * U,  if UPLO = 'U', or
    A = L * L**T,  if UPLO = 'L',
 where U is an upper triangular band matrix, and L is a lower
 triangular band matrix, with the same number of superdiagonals or
 subdiagonals as A.  The factored form of A is then used to solve the
 system of equations A * X = B.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangle of A is stored;
          = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
          The number of linear equations, i.e., 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,out]AB
          AB is DOUBLE PRECISION array, dimension (LDAB,N)
          On entry, the upper or lower triangle of the symmetric band
          matrix A, stored in the first KD+1 rows of the array.  The
          j-th column of A is stored in the j-th column of the array AB
          as follows:
          if UPLO = 'U', AB(KD+1+i-j,j) = A(i,j) for max(1,j-KD)<=i<=j;
          if UPLO = 'L', AB(1+i-j,j)    = A(i,j) for j<=i<=min(N,j+KD).
          See below for further details.

          On exit, if INFO = 0, the triangular factor U or L from the
          Cholesky factorization A = U**T*U or A = L*L**T of the band
          matrix A, in the same storage format as A.
[in]LDAB
          LDAB is INTEGER
          The leading dimension of the array AB.  LDAB >= KD+1.
[in,out]B
          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
          On entry, the N-by-NRHS right hand side matrix B.
          On exit, if INFO = 0, the N-by-NRHS 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
          > 0:  if INFO = i, the leading principal minor of order i
                of A is not positive, so the factorization could not
                be completed, and the solution has not been computed.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  The band storage scheme is illustrated by the following example, when
  N = 6, KD = 2, and UPLO = 'U':

  On entry:                       On exit:

      *    *   a13  a24  a35  a46      *    *   u13  u24  u35  u46
      *   a12  a23  a34  a45  a56      *   u12  u23  u34  u45  u56
     a11  a22  a33  a44  a55  a66     u11  u22  u33  u44  u55  u66

  Similarly, if UPLO = 'L' the format of A is as follows:

  On entry:                       On exit:

     a11  a22  a33  a44  a55  a66     l11  l22  l33  l44  l55  l66
     a21  a32  a43  a54  a65   *      l21  l32  l43  l54  l65   *
     a31  a42  a53  a64   *    *      l31  l42  l53  l64   *    *

  Array elements marked * are not used by the routine.

Definition at line 163 of file dpbsv.f.

164*
165* -- LAPACK driver routine --
166* -- LAPACK is a software package provided by Univ. of Tennessee, --
167* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168*
169* .. Scalar Arguments ..
170 CHARACTER UPLO
171 INTEGER INFO, KD, LDAB, LDB, N, NRHS
172* ..
173* .. Array Arguments ..
174 DOUBLE PRECISION AB( LDAB, * ), B( LDB, * )
175* ..
176*
177* =====================================================================
178*
179* .. External Functions ..
180 LOGICAL LSAME
181 EXTERNAL lsame
182* ..
183* .. External Subroutines ..
184 EXTERNAL dpbtrf, dpbtrs, xerbla
185* ..
186* .. Intrinsic Functions ..
187 INTRINSIC max
188* ..
189* .. Executable Statements ..
190*
191* Test the input parameters.
192*
193 info = 0
194 IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
195 info = -1
196 ELSE IF( n.LT.0 ) THEN
197 info = -2
198 ELSE IF( kd.LT.0 ) THEN
199 info = -3
200 ELSE IF( nrhs.LT.0 ) THEN
201 info = -4
202 ELSE IF( ldab.LT.kd+1 ) THEN
203 info = -6
204 ELSE IF( ldb.LT.max( 1, n ) ) THEN
205 info = -8
206 END IF
207 IF( info.NE.0 ) THEN
208 CALL xerbla( 'DPBSV ', -info )
209 RETURN
210 END IF
211*
212* Compute the Cholesky factorization A = U**T*U or A = L*L**T.
213*
214 CALL dpbtrf( uplo, n, kd, ab, ldab, info )
215 IF( info.EQ.0 ) THEN
216*
217* Solve the system A*X = B, overwriting B with X.
218*
219 CALL dpbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
220*
221 END IF
222 RETURN
223*
224* End of DPBSV
225*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dpbtrf(uplo, n, kd, ab, ldab, info)
DPBTRF
Definition dpbtrf.f:142
subroutine dpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
DPBTRS
Definition dpbtrs.f:121
Here is the call graph for this function:
Here is the caller graph for this function: