Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgtts2 (3p)

Name

dgtts2 - solve a system of linear equations with a tridiagonal matrix using the LU factorization computed by dgttrf

Synopsis

SUBROUTINE DGTTS2(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


INTEGER ITRANS, LDB, N, NRHS

INTEGER IPIV(*)

DOUBLE PRECISION B(LDB,*), D(*), DL(*), DU(*), DU2(*)


SUBROUTINE DGTTS2_64(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


INTEGER*8 ITRANS, LDB, N, NRHS

INTEGER*8 IPIV(*)

DOUBLE PRECISION B(LDB,*), D(*), DL(*), DU(*), DU2(*)


F95 INTERFACE
SUBROUTINE GTTS2(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


REAL(8), DIMENSION(:,:) :: B

INTEGER :: ITRANS, N, NRHS, LDB

INTEGER, DIMENSION(:) :: IPIV

REAL(8), DIMENSION(:) :: DL, D, DU, DU2


SUBROUTINE GTTS2_64(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


REAL(8), DIMENSION(:,:) :: B

INTEGER(8) :: ITRANS, N, NRHS, LDB

INTEGER(8), DIMENSION(:) :: IPIV

REAL(8), DIMENSION(:) :: DL, D, DU, DU2


C INTERFACE
#include <sunperf.h>

void dgtts2 (int itrans, int n, int nrhs, double *dl, double *d, double
*du, double *du2, int *ipiv, double *b, int ldb);


void  dgtts2_64 (long itrans, long n, long nrhs, double *dl, double *d,
double *du, double *du2, long *ipiv, double *b, long ldb);

Description

Oracle Solaris Studio Performance Library                           dgtts2(3P)



NAME
       dgtts2  -  solve a system of linear equations with a tridiagonal matrix
       using the LU factorization computed by dgttrf


SYNOPSIS
       SUBROUTINE DGTTS2(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


       INTEGER ITRANS, LDB, N, NRHS

       INTEGER IPIV(*)

       DOUBLE PRECISION B(LDB,*), D(*), DL(*), DU(*), DU2(*)


       SUBROUTINE DGTTS2_64(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


       INTEGER*8 ITRANS, LDB, N, NRHS

       INTEGER*8 IPIV(*)

       DOUBLE PRECISION B(LDB,*), D(*), DL(*), DU(*), DU2(*)


   F95 INTERFACE
       SUBROUTINE GTTS2(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


       REAL(8), DIMENSION(:,:) :: B

       INTEGER :: ITRANS, N, NRHS, LDB

       INTEGER, DIMENSION(:) :: IPIV

       REAL(8), DIMENSION(:) :: DL, D, DU, DU2


       SUBROUTINE GTTS2_64(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)


       REAL(8), DIMENSION(:,:) :: B

       INTEGER(8) :: ITRANS, N, NRHS, LDB

       INTEGER(8), DIMENSION(:) :: IPIV

       REAL(8), DIMENSION(:) :: DL, D, DU, DU2


   C INTERFACE
       #include <sunperf.h>

       void dgtts2 (int itrans, int n, int nrhs, double *dl, double *d, double
                 *du, double *du2, int *ipiv, double *b, int ldb);


       void  dgtts2_64 (long itrans, long n, long nrhs, double *dl, double *d,
                 double *du, double *du2, long *ipiv, double *b, long ldb);


PURPOSE
       dgtts2 solves one of the systems of equations A*X=B  or  A**T*X=B, with
       a tridiagonal matrix A using the LU factorization computed by DGTTRF.



ARGUMENTS
       ITRANS (input)
                 ITRANS is INTEGER
                 Specifies the form of the system of equations.
                 = 0:  A * X = B  (No transpose),
                 = 1:  A**T* X = B  (Transpose),
                 = 2:  A**T* X = B  (Conjugate transpose = Transpose).


       N (input)
                 N is INTEGER
                 The order of the matrix A.


       NRHS (input)
                 NRHS is INTEGER
                 The  number  of right hand sides, i.e., the number of columns
                 of the matrix B. NRHS >= 0.


       DL (input)
                 DL is DOUBLE PRECISION array, dimension (N-1)
                 The (N-1) multipliers that define the matrix L  from  the  LU
                 factorization of A.


       D (input)
                 D is DOUBLE PRECISION array, dimension (N)
                 The N diagonal elements of the upper triangular matrix U from
                 the LU factorization of A.


       DU (input)
                 DU is DOUBLE PRECISION array, dimension (N-1)
                 The (N-1) elements of the first super-diagonal of U.


       DU2 (input)
                 DU2 is DOUBLE PRECISION array, dimension (N-2)
                 The (N-2) elements of the second super-diagonal of U.


       IPIV (input)
                 IPIV is INTEGER array, dimension (N)
                 The pivot indices; for 1 <= i <= N, row i of the  matrix  was
                 interchanged  with row IPIV(i). IPIV(i) will always be either
                 i or i+1; IPIV(i) = i indicates a  row  interchange  was  not
                 required.


       B (input/output)
                 B is DOUBLE PRECISION array, dimension (LDB,NRHS)
                 On entry, the matrix of right hand side vectors B.
                 On exit, B is overwritten by the solution vectors X.


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



                                  7 Nov 2015                        dgtts2(3P)