Contents


NAME

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

SYNOPSIS

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

     CHARACTER * 1 UPLO
     COMPLEX OFFD(*), OFFDF(*), B(LDB,*), X(LDX,*), WORK(*)
     INTEGER N, NRHS, LDB, LDX, INFO
     REAL DIAG(*), DIAGF(*), FERR(*), BERR(*), WORK2(*)

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

     CHARACTER * 1 UPLO
     COMPLEX OFFD(*), OFFDF(*), B(LDB,*), X(LDX,*), WORK(*)
     INTEGER*8 N, NRHS, LDB, LDX, INFO
     REAL DIAG(*), DIAGF(*), FERR(*), BERR(*), WORK2(*)

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

     CHARACTER(LEN=1) :: UPLO
     COMPLEX, DIMENSION(:) :: OFFD, OFFDF, WORK
     COMPLEX, DIMENSION(:,:) :: B, X
     INTEGER :: N, NRHS, LDB, LDX, INFO
     REAL, DIMENSION(:) :: DIAG, DIAGF, FERR, BERR, WORK2

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

     CHARACTER(LEN=1) :: UPLO
     COMPLEX, DIMENSION(:) :: OFFD, OFFDF, WORK
     COMPLEX, DIMENSION(:,:) :: B, X
     INTEGER(8) :: N, NRHS, LDB, LDX, INFO
     REAL, DIMENSION(:) :: DIAG, DIAGF, FERR, BERR, WORK2

  C INTERFACE
     #include <sunperf.h>

     void cptrfs(char uplo, int n, int nrhs, float *diag, complex
               *offd,  float  *diagf, complex *offdf, complex *b,
               int ldb, complex *x, int ldx, float  *ferr,  float
               *berr, int *info);

     void cptrfs_64(char uplo, long n, long  nrhs,  float  *diag,
               complex  *offd, float *diagf, complex *offdf, com-
               plex *b, long ldb, complex  *x,  long  ldx,  float
               *ferr, float *berr, long *info);

PURPOSE

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

ARGUMENTS

     UPLO (input)
               Specifies whether the superdiagonal or the  subdi-
               agonal  of  the tridiagonal matrix A is stored and
               the form of the factorization:
               = 'U':  OFFD is the superdiagonal of A,  and  A  =
               U**H*DIAG*U;
               = 'L':  OFFD is the subdiagonal  of  A,  and  A  =
               L*DIAG*L**H.   (The  two forms are equivalent if A
               is real.)

     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 real diagonal elements  of  the  tridiagonal
               matrix A.

     OFFD (input)
               The (n-1) off-diagonal elements of the tridiagonal
               matrix A (see UPLO).

     DIAGF (input)
               The n diagonal elements  of  the  diagonal  matrix
               DIAG from the factorization computed by CPTTRF.
     OFFDF (input)
               The (n-1) off-diagonal elements of the unit  bidi-
               agonal  factor  U or L from the factorization com-
               puted by CPTTRF (see UPLO).

     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
               CPTTRS.  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(N)

     WORK2 (workspace)
               dimension(N)

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