Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

ztprfs (3p)

Name

ztprfs - provide error bounds and backward error estimates for the solution to a system of linear equations with a triangular packed coef- ficient matrix

Synopsis

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

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

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

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




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
COMPLEX(8), DIMENSION(:) :: A, WORK
COMPLEX(8), DIMENSION(:,:) :: B, X
INTEGER :: N, NRHS, LDB, LDX, INFO
REAL(8), DIMENSION(:) :: FERR, BERR, WORK2

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

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




C INTERFACE
#include <sunperf.h>

void ztprfs(char uplo, char transa, char diag, int n, int nrhs, double-
complex *a, doublecomplex *b, int ldb, doublecomplex *x,  int
ldx, double *ferr, double *berr, int *info);

void  ztprfs_64(char  uplo,  char transa, char diag, long n, long nrhs,
doublecomplex *a, doublecomplex *b, long  ldb,  doublecomplex
*x, long ldx, double *ferr, double *berr, long *info);

Description

Oracle Solaris Studio Performance Library                           ztprfs(3P)



NAME
       ztprfs  -  provide  error  bounds  and backward error estimates for the
       solution to a system of linear equations with a triangular packed coef-
       ficient matrix


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

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

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

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




   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
       COMPLEX(8), DIMENSION(:) :: A, WORK
       COMPLEX(8), DIMENSION(:,:) :: B, X
       INTEGER :: N, NRHS, LDB, LDX, INFO
       REAL(8), DIMENSION(:) :: FERR, BERR, WORK2

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

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




   C INTERFACE
       #include <sunperf.h>

       void ztprfs(char uplo, char transa, char diag, int n, int nrhs, double-
                 complex *a, doublecomplex *b, int ldb, doublecomplex *x,  int
                 ldx, double *ferr, double *berr, int *info);

       void  ztprfs_64(char  uplo,  char transa, char diag, long n, long nrhs,
                 doublecomplex *a, doublecomplex *b, long  ldb,  doublecomplex
                 *x, long ldx, double *ferr, double *berr, long *info);



PURPOSE
       ztprfs provides error bounds and backward error estimates for the solu-
       tion to a system of linear equations with a triangular  packed  coeffi-
       cient matrix.

       The  solution  matrix  X must be computed by ZTPTRS or some other means
       before entering this routine.  ZTPRFS 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)


       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) COMPLEX*16 array, dimension (N*(N+1)/2)
                 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)*(2n-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) COMPLEX*16 array, dimension (LDB,NRHS)
                 The right hand side matrix B.


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


       X (input) COMPLEX*16 array, dimension (LDX,NRHS)
                 The solution matrix X.


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


       FERR (output) DOUBLE PRECISION array, dimension (NRHS)
                 The  estimated  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 esti-
                 mated upper bound for the magnitude of the largest element in
                 (X(j)  -  XTRUE) divided by the magnitude of the largest ele-
                 ment 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) DOUBLE PRECISION array, dimension (NRHS)
                 The componentwise relative backward error  of  each  solution
                 vector  X(j)  (i.e., the smallest relative change in any ele-
                 ment of A or B that makes X(j) an exact solution).


       WORK (workspace)
                 COMPLEX*16 array, dimension(2*N)

       WORK2 (workspace)
                 DOUBLE PRECISION array, dimension(N)


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




                                  7 Nov 2015                        ztprfs(3P)