Contents


NAME

     cgbrfs - improve the computed solution to a system of linear
     equations  when  the  coefficient matrix is banded, and pro-
     vides error bounds and  backward  error  estimates  for  the
     solution

SYNOPSIS

     SUBROUTINE CGBRFS(TRANSA, N, KL, KU, NRHS, A, LDA, AF, LDAF,
           IPIVOT, B, LDB, X, LDX, FERR, BERR, WORK, WORK2, INFO)

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

     SUBROUTINE CGBRFS_64(TRANSA, N, KL, KU, NRHS, A, LDA, AF, LDAF,
           IPIVOT, B, LDB, X, LDX, FERR, BERR, WORK, WORK2, INFO)

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

  F95 INTERFACE
     SUBROUTINE GBRFS([TRANSA], [N], KL, KU, [NRHS], A, [LDA], AF,
            [LDAF], IPIVOT, B, [LDB], X, [LDX], FERR, BERR, [WORK], [WORK2],
            [INFO])

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

     SUBROUTINE GBRFS_64([TRANSA], [N], KL, KU, [NRHS], A, [LDA],
            AF, [LDAF], IPIVOT, B, [LDB], X, [LDX], FERR, BERR, [WORK],
            [WORK2], [INFO])

     CHARACTER(LEN=1) :: TRANSA
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A, AF, B, X
     INTEGER(8) :: N, KL, KU, NRHS, LDA, LDAF, LDB, LDX, INFO
     INTEGER(8), DIMENSION(:) :: IPIVOT
     REAL, DIMENSION(:) :: FERR, BERR, WORK2
  C INTERFACE
     #include <sunperf.h>

     void cgbrfs(char transa, int n, int kl, int  ku,  int  nrhs,
               complex  *a,  int  lda, complex *af, int ldaf, int
               *ipivot, complex *b, int ldb, complex *x, int ldx,
               float *ferr, float *berr, int *info);

     void cgbrfs_64(char transa, long n, long kl, long  ku,  long
               nrhs,  complex  *a,  long  lda,  complex *af, long
               ldaf, long *ipivot, complex *b, long ldb,  complex
               *x,  long  ldx,  float  *ferr,  float  *berr, long
               *info);

PURPOSE

     cgbrfs improves the computed solution to a system of  linear
     equations  when  the  coefficient matrix is banded, and pro-
     vides error bounds and  backward  error  estimates  for  the
     solution.

ARGUMENTS

     TRANSA (input)
               Specifies the form of the system of equations:
               = 'N':  A * X = B     (No transpose)
               = 'T':  A**T * X = B  (Transpose)
               = 'C':  A**H * X = B  (Conjugate transpose)

               TRANSA is defaulted to 'N' for F95 INTERFACE.

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

     KL (input)
               The number of subdiagonals within the band  of  A.
               KL >= 0.

     KU (input)
               The number of superdiagonals within the band of A.
               KU >= 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 original band matrix A, stored in  rows  1  to
               KL+KU+1.   The  j-th  column of A is stored in the
               j-th column of the array A as follows:   A(ku+1+i-
               j,j) = A(i,j) for max(1,j-ku)<=i<=min(n,j+kl).

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

     AF (input)
               Details of the LU factorization of the band matrix
               A, as computed by CGBTRF.  U is stored as an upper
               triangular band matrix with  KL+KU  superdiagonals
               in  rows  1  to  KL+KU+1, and the multipliers used
               during  the  factorization  are  stored  in   rows
               KL+KU+2 to 2*KL+KU+1.

     LDAF (input)
               The leading dimension of the array  AF.   LDAF  >=
               2*KL*KU+1.

     IPIVOT (input)
               The pivot indices from CGBTRF; for 1<=i<=N, row  i
               of the matrix was interchanged with row IPIVOT(i).

     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
               CGBTRS.  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