Contents


NAME

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

SYNOPSIS

     SUBROUTINE DPTRFS(N, NRHS, DIAG, OFFD, DIAGF, OFFDF, B, LDB, X, LDX,
           FERR, BERR, WORK, INFO)

     INTEGER N, NRHS, LDB, LDX, INFO
     DOUBLE  PRECISION  DIAG(*),  OFFD(*),  DIAGF(*),   OFFDF(*),
     B(LDB,*), X(LDX,*), FERR(*), BERR(*), WORK(*)

     SUBROUTINE DPTRFS_64(N, NRHS, DIAG, OFFD, DIAGF, OFFDF, B, LDB, X,
           LDX, FERR, BERR, WORK, INFO)

     INTEGER*8 N, NRHS, LDB, LDX, INFO
     DOUBLE  PRECISION  DIAG(*),  OFFD(*),  DIAGF(*),   OFFDF(*),
     B(LDB,*), X(LDX,*), FERR(*), BERR(*), WORK(*)

  F95 INTERFACE
     SUBROUTINE PTRFS([N], [NRHS], DIAG, OFFD, DIAGF, OFFDF, B, [LDB], X,
            [LDX], FERR, BERR, [WORK], [INFO])

     INTEGER :: N, NRHS, LDB, LDX, INFO
     REAL(8), DIMENSION(:) :: DIAG,  OFFD,  DIAGF,  OFFDF,  FERR,
     BERR, WORK
     REAL(8), DIMENSION(:,:) :: B, X

     SUBROUTINE PTRFS_64([N], [NRHS], DIAG, OFFD, DIAGF, OFFDF, B, [LDB],
            X, [LDX], FERR, BERR, [WORK], [INFO])

     INTEGER(8) :: N, NRHS, LDB, LDX, INFO
     REAL(8), DIMENSION(:) :: DIAG,  OFFD,  DIAGF,  OFFDF,  FERR,
     BERR, WORK
     REAL(8), DIMENSION(:,:) :: B, X

  C INTERFACE
     #include <sunperf.h>

     void dptrfs(int n, int nrhs,  double  *diag,  double  *offd,
               double  *diagf, double *offdf, double *b, int ldb,
               double *x, int ldx, double  *ferr,  double  *berr,
               int *info);
     void dptrfs_64(long  n,  long  nrhs,  double  *diag,  double
               *offd,  double  *diagf,  double *offdf, double *b,
               long ldb, double *x, long ldx, double *ferr,  dou-
               ble *berr, long *info);

PURPOSE

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

ARGUMENTS

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

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

     DIAG (input)
               The n diagonal elements of the tridiagonal  matrix
               A.

     OFFD (input)
               The (n-1) subdiagonal elements of the  tridiagonal
               matrix A.

     DIAGF (input)
               The n diagonal elements  of  the  diagonal  matrix
               DIAG from the factorization computed by SPTTRF.

     OFFDF (input)
               The (n-1) subdiagonal elements of the unit bidiag-
               onal  factor  L from the factorization computed by
               SPTTRF.

     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
               SPTTRS.  On exit, the improved solution matrix X.

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

     FERR (output)
               The forward error bound for each  solution  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 element in (X(j) - XTRUE)
               divided by the magnitude of the largest element in
               X(j).

     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)

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