zgtrfs


NAME

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


SYNOPSIS

  SUBROUTINE ZGTRFS( TRANSA, N, NRHS, LOW, DIAG, UP, LOWF, DIAGF, 
 *      UPF1, UPF2, IPIVOT, B, LDB, X, LDX, FERR, BERR, WORK, WORK2, 
 *      INFO)
  CHARACTER * 1 TRANSA
  DOUBLE COMPLEX LOW(*), DIAG(*), UP(*), LOWF(*), DIAGF(*), UPF1(*), UPF2(*), B(LDB,*), X(LDX,*), WORK(*)
  INTEGER N, NRHS, LDB, LDX, INFO
  INTEGER IPIVOT(*)
  DOUBLE PRECISION FERR(*), BERR(*), WORK2(*)
 
  SUBROUTINE ZGTRFS_64( TRANSA, N, NRHS, LOW, DIAG, UP, LOWF, DIAGF, 
 *      UPF1, UPF2, IPIVOT, B, LDB, X, LDX, FERR, BERR, WORK, WORK2, 
 *      INFO)
  CHARACTER * 1 TRANSA
  DOUBLE COMPLEX LOW(*), DIAG(*), UP(*), LOWF(*), DIAGF(*), UPF1(*), UPF2(*), B(LDB,*), X(LDX,*), WORK(*)
  INTEGER*8 N, NRHS, LDB, LDX, INFO
  INTEGER*8 IPIVOT(*)
  DOUBLE PRECISION FERR(*), BERR(*), WORK2(*)
 

F95 INTERFACE

  SUBROUTINE GTRFS( [TRANSA], [N], [NRHS], LOW, DIAG, UP, LOWF, DIAGF, 
 *       UPF1, UPF2, IPIVOT, B, [LDB], X, [LDX], FERR, BERR, [WORK], 
 *       [WORK2], [INFO])
  CHARACTER(LEN=1) :: TRANSA
  COMPLEX(8), DIMENSION(:) :: LOW, DIAG, UP, LOWF, DIAGF, UPF1, UPF2, WORK
  COMPLEX(8), DIMENSION(:,:) :: B, X
  INTEGER :: N, NRHS, LDB, LDX, INFO
  INTEGER, DIMENSION(:) :: IPIVOT
  REAL(8), DIMENSION(:) :: FERR, BERR, WORK2
 
  SUBROUTINE GTRFS_64( [TRANSA], [N], [NRHS], LOW, DIAG, UP, LOWF, 
 *       DIAGF, UPF1, UPF2, IPIVOT, B, [LDB], X, [LDX], FERR, BERR, [WORK], 
 *       [WORK2], [INFO])
  CHARACTER(LEN=1) :: TRANSA
  COMPLEX(8), DIMENSION(:) :: LOW, DIAG, UP, LOWF, DIAGF, UPF1, UPF2, WORK
  COMPLEX(8), DIMENSION(:,:) :: B, X
  INTEGER(8) :: N, NRHS, LDB, LDX, INFO
  INTEGER(8), DIMENSION(:) :: IPIVOT
  REAL(8), DIMENSION(:) :: FERR, BERR, WORK2
 

C INTERFACE

#include <sunperf.h>

void zgtrfs(char transa, int n, int nrhs, doublecomplex *low, doublecomplex *diag, doublecomplex *up, doublecomplex *lowf, doublecomplex *diagf, doublecomplex *upf1, doublecomplex *upf2, int *ipivot, doublecomplex *b, int ldb, doublecomplex *x, int ldx, double *ferr, double *berr, int *info);

void zgtrfs_64(char transa, long n, long nrhs, doublecomplex *low, doublecomplex *diag, doublecomplex *up, doublecomplex *lowf, doublecomplex *diagf, doublecomplex *upf1, doublecomplex *upf2, long *ipivot, doublecomplex *b, long ldb, doublecomplex *x, long ldx, double *ferr, double *berr, long *info);


PURPOSE

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


ARGUMENTS

* TRANSA (input)
Specifies the form of the system of equations:

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

* LOW (input)
The (n-1) subdiagonal elements of A.

* DIAG (input)
The diagonal elements of A.

* UP (input)
The (n-1) superdiagonal elements of A.

* LOWF (input)
The (n-1) multipliers that define the matrix L from the LU factorization of A as computed by CGTTRF.

* DIAGF (input)
The n diagonal elements of the upper triangular matrix U from the LU factorization of A.

* UPF1 (input)
The (n-1) elements of the first superdiagonal of U.

* UPF2 (input)
The (n-2) elements of the second superdiagonal of U.

* IPIVOT (input)
The pivot indices; for 1 <= i <= n, row i of the matrix was interchanged with row IPIVOT(i). IPIVOT(i) will always be either i or i+1; IPIVOT(i) = i indicates a row interchange was not required.

* 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 CGTTRS. 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 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). 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)
* INFO (output)