Contents


NAME

     cpbrfs - improve the computed solution to a system of linear
     equations  when the coefficient matrix is Hermitian positive
     definite and banded, and provides error bounds and  backward
     error estimates for the solution

SYNOPSIS

     SUBROUTINE CPBRFS(UPLO, N, KD, NRHS, A, LDA, AF, LDAF, B, LDB, X,
           LDX, FERR, BERR, WORK, WORK2, INFO)

     CHARACTER * 1 UPLO
     COMPLEX A(LDA,*), AF(LDAF,*), B(LDB,*), X(LDX,*), WORK(*)
     INTEGER N, KD, NRHS, LDA, LDAF, LDB, LDX, INFO
     REAL FERR(*), BERR(*), WORK2(*)

     SUBROUTINE CPBRFS_64(UPLO, N, KD, NRHS, A, LDA, AF, LDAF, B, LDB,
           X, LDX, FERR, BERR, WORK, WORK2, INFO)

     CHARACTER * 1 UPLO
     COMPLEX A(LDA,*), AF(LDAF,*), B(LDB,*), X(LDX,*), WORK(*)
     INTEGER*8 N, KD, NRHS, LDA, LDAF, LDB, LDX, INFO
     REAL FERR(*), BERR(*), WORK2(*)

  F95 INTERFACE
     SUBROUTINE PBRFS(UPLO, [N], KD, [NRHS], A, [LDA], AF, [LDAF], B,
            [LDB], X, [LDX], FERR, BERR, [WORK], [WORK2], [INFO])

     CHARACTER(LEN=1) :: UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A, AF, B, X
     INTEGER :: N, KD, NRHS, LDA, LDAF, LDB, LDX, INFO
     REAL, DIMENSION(:) :: FERR, BERR, WORK2

     SUBROUTINE PBRFS_64(UPLO, [N], KD, [NRHS], A, [LDA], AF, [LDAF],
            B, [LDB], X, [LDX], FERR, BERR, [WORK], [WORK2], [INFO])

     CHARACTER(LEN=1) :: UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A, AF, B, X
     INTEGER(8) :: N, KD, NRHS, LDA, LDAF, LDB, LDX, INFO
     REAL, DIMENSION(:) :: FERR, BERR, WORK2

  C INTERFACE
     #include <sunperf.h>

     void cpbrfs(char uplo, int n, int kd, int nrhs, complex  *a,
               int  lda,  complex  *af, int ldaf, complex *b, int
               ldb, complex  *x,  int  ldx,  float  *ferr,  float
               *berr, int *info);

     void cpbrfs_64(char uplo, long n, long kd, long  nrhs,  com-
               plex *a, long lda, complex *af, long ldaf, complex
               *b, long ldb, complex *x, long ldx,  float  *ferr,
               float *berr, long *info);

PURPOSE

     cpbrfs improves the computed solution to a system of  linear
     equations  when the coefficient matrix is Hermitian positive
     definite and banded, and provides error bounds and  backward
     error estimates for the solution.

ARGUMENTS

     UPLO (input)
               = 'U':  Upper triangle of A is stored;
               = 'L':  Lower triangle of A is stored.

     N (input) The order of the matrix A.  N >= 0.

     KD (input)
               The number of superdiagonals of the  matrix  A  if
               UPLO  = 'U', or the number of subdiagonals if UPLO
               = 'L'.  KD >= 0.

     NRHS (input)
               The number of right hand sides, i.e.,  the  number
               of columns of the matrices B and X.  NRHS >= 0.

     A (input) The upper or lower triangle of the Hermitian  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 A as follows:  if UPLO = 'U',
               A(kd+1+i-j,j) = A(i,j) for  max(1,j-kd)<=i<=j;  if
               UPLO   =   'L',   A(1+i-j,j)      =   A(i,j)   for
               j<=i<=min(n,j+kd).

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               KD+1.

     AF (input)
               The triangular factor U or  L  from  the  Cholesky
               factorization A = U**H*U or A = L*L**H of the band
               matrix A  as  computed  by  CPBTRF,  in  the  same
               storage format as A (see A).

     LDAF (input)
               The leading dimension of the array  AF.   LDAF  >=
               KD+1.

     B (input) The right hand side matrix B.

     LDB (input)
               The leading dimension of  the  array  B.   LDB  >=
               max(1,N).

     X (input/output)
               On entry, the solution matrix X,  as  computed  by
               CPBTRS.  On exit, the improved solution matrix X.

     LDX (input)
               The leading dimension of  the  array  X.   LDX  >=
               max(1,N).

     FERR (output)
               The estimated forward error bound for  each  solu-
               tion  vector X(j) (the j-th column of the solution
               matrix  X).   If  XTRUE  is  the   true   solution
               corresponding  to  X(j),  FERR(j)  is an estimated
               upper bound for the magnitude of the largest  ele-
               ment in (X(j) - XTRUE) divided by the magnitude of
               the largest element in X(j).  The estimate  is  as
               reliable  as the estimate for RCOND, and is almost
               always a slight overestimate of the true error.

     BERR (output)
               The componentwise relative backward error of  each
               solution  vector X(j) (i.e., the smallest relative
               change in any element of A or B that makes X(j) an
               exact solution).

     WORK (workspace)
               dimension(2*N)

     WORK2 (workspace)
               dimension(N)

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value