Contents


NAME

     stprfs - provide error bounds and backward  error  estimates
     for the solution to a system of linear equations with a tri-
     angular packed coefficient matrix

SYNOPSIS

     SUBROUTINE STPRFS(UPLO, TRANSA, DIAG, N, NRHS, A, B, LDB, X, LDX,
           FERR, BERR, WORK, WORK2, INFO)

     CHARACTER * 1 UPLO, TRANSA, DIAG
     INTEGER N, NRHS, LDB, LDX, INFO
     INTEGER WORK2(*)
     REAL A(*), B(LDB,*), X(LDX,*), FERR(*), BERR(*), WORK(*)

     SUBROUTINE STPRFS_64(UPLO, TRANSA, DIAG, N, NRHS, A, B, LDB, X, LDX,
           FERR, BERR, WORK, WORK2, INFO)

     CHARACTER * 1 UPLO, TRANSA, DIAG
     INTEGER*8 N, NRHS, LDB, LDX, INFO
     INTEGER*8 WORK2(*)
     REAL A(*), B(LDB,*), X(LDX,*), FERR(*), BERR(*), WORK(*)

  F95 INTERFACE
     SUBROUTINE TPRFS(UPLO, [TRANSA], DIAG, N, NRHS, A, B, [LDB], X, [LDX],
            FERR, BERR, [WORK], [WORK2], [INFO])

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

     SUBROUTINE TPRFS_64(UPLO, [TRANSA], DIAG, N, NRHS, A, B, [LDB], X,
            [LDX], FERR, BERR, [WORK], [WORK2], [INFO])

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

  C INTERFACE
     #include <sunperf.h>

     void stprfs(char uplo, char transa, char diag,  int  n,  int
               nrhs,  float  *a, float *b, int ldb, float *x, int
               ldx, float *ferr, float *berr, int *info);
     void stprfs_64(char uplo, char transa, char  diag,  long  n,
               long nrhs, float *a, float *b, long ldb, float *x,
               long ldx, float *ferr, float *berr, long *info);

PURPOSE

     stprfs provides error bounds and  backward  error  estimates
     for the solution to a system of linear equations with a tri-
     angular packed coefficient matrix.

     The solution matrix X must be computed  by  STPTRS  or  some
     other  means  before entering this routine.  STPRFS does not
     do iterative refinement because doing so cannot improve  the
     backward error.

ARGUMENTS

     UPLO (input)
               = 'U':  A is upper triangular;
               = 'L':  A is lower triangular.

     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 = Tran-
               spose)

               TRANSA is defaulted to 'N' for F95 INTERFACE.

     DIAG (input)
               = 'N':  A is non-unit triangular;
               = 'U':  A is unit triangular.

     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 matrices B and X.  NRHS >= 0.

     A (input) The upper or lower  triangular  matrix  A,  packed
               columnwise  in a linear array.  The j-th column of
               A is stored in the array A as follows:  if UPLO  =
               'U',  A(i  +  (j-1)*j/2)  = A(i,j) for 1<=i<=j; if
               UPLO = 'L', A(i + (j-1)*(2*n-j)/2)  =  A(i,j)  for
               j<=i<=n.   If DIAG = 'U', the diagonal elements of
               A are not referenced and are assumed to be 1.

     B (input) The right hand side matrix B.

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

     X (input) The 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(3*N)

     WORK2 (workspace)
               dimension(N)

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