dgttrs


NAME

dgttrs - solve one of the systems of equations A*X = B or A'*X = B,


SYNOPSIS

  SUBROUTINE DGTTRS( TRANSA, N, NRHS, LOW, DIAG, UP1, UP2, IPIVOT, B, 
 *      LDB, INFO)
  CHARACTER * 1 TRANSA
  INTEGER N, NRHS, LDB, INFO
  INTEGER IPIVOT(*)
  DOUBLE PRECISION LOW(*), DIAG(*), UP1(*), UP2(*), B(LDB,*)
 
  SUBROUTINE DGTTRS_64( TRANSA, N, NRHS, LOW, DIAG, UP1, UP2, IPIVOT, 
 *      B, LDB, INFO)
  CHARACTER * 1 TRANSA
  INTEGER*8 N, NRHS, LDB, INFO
  INTEGER*8 IPIVOT(*)
  DOUBLE PRECISION LOW(*), DIAG(*), UP1(*), UP2(*), B(LDB,*)
 

F95 INTERFACE

  SUBROUTINE GTTRS( [TRANSA], [N], [NRHS], LOW, DIAG, UP1, UP2, 
 *       IPIVOT, B, [LDB], [INFO])
  CHARACTER(LEN=1) :: TRANSA
  INTEGER :: N, NRHS, LDB, INFO
  INTEGER, DIMENSION(:) :: IPIVOT
  REAL(8), DIMENSION(:) :: LOW, DIAG, UP1, UP2
  REAL(8), DIMENSION(:,:) :: B
 
  SUBROUTINE GTTRS_64( [TRANSA], [N], [NRHS], LOW, DIAG, UP1, UP2, 
 *       IPIVOT, B, [LDB], [INFO])
  CHARACTER(LEN=1) :: TRANSA
  INTEGER(8) :: N, NRHS, LDB, INFO
  INTEGER(8), DIMENSION(:) :: IPIVOT
  REAL(8), DIMENSION(:) :: LOW, DIAG, UP1, UP2
  REAL(8), DIMENSION(:,:) :: B
 

C INTERFACE

#include <sunperf.h>

void dgttrs(char transa, int n, int nrhs, double *low, double *diag, double *up1, double *up2, int *ipivot, double *b, int ldb, int *info);

void dgttrs_64(char transa, long n, long nrhs, double *low, double *diag, double *up1, double *up2, long *ipivot, double *b, long ldb, long *info);


PURPOSE

dgttrs solves one of the systems of equations A*X = B or A'*X = B, with a tridiagonal matrix A using the LU factorization computed by SGTTRF.


ARGUMENTS

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

* N (input)
The order of the matrix A.

* 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) multipliers that define the matrix L from the LU factorization of A.

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

* UP1 (input)
The (n-1) elements of the first super-diagonal of U.

* UP2 (input)
The (n-2) elements of the second super-diagonal 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/output)
On entry, the matrix of right hand side vectors B. On exit, B is overwritten by the solution vectors X.

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

* INFO (output)