Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgtsv (3p)

Name

dgtsv - N tridiagonal matrix, by Gaussian elimination with partial pivoting

Synopsis

SUBROUTINE DGTSV(N, NRHS, LOW, D, UP, B, LDB, INFO)

INTEGER N, NRHS, LDB, INFO
DOUBLE PRECISION LOW(*), D(*), UP(*), B(LDB,*)

SUBROUTINE DGTSV_64(N, NRHS, LOW, D, UP, B, LDB, INFO)

INTEGER*8 N, NRHS, LDB, INFO
DOUBLE PRECISION LOW(*), D(*), UP(*), B(LDB,*)




F95 INTERFACE
SUBROUTINE GTSV(N, NRHS, LOW, D, UP, B, LDB, INFO)

INTEGER :: N, NRHS, LDB, INFO
REAL(8), DIMENSION(:) :: LOW, D, UP
REAL(8), DIMENSION(:,:) :: B

SUBROUTINE GTSV_64(N, NRHS, LOW, D, UP, B, LDB, INFO)

INTEGER(8) :: N, NRHS, LDB, INFO
REAL(8), DIMENSION(:) :: LOW, D, UP
REAL(8), DIMENSION(:,:) :: B




C INTERFACE
#include <sunperf.h>

void dgtsv(int n, int nrhs, double *low, double *d, double *up,  double
*b, int ldb, int *info);

void  dgtsv_64(long  n,  long nrhs, double *low, double *d, double *up,
double *b, long ldb, long *info);

Description

Oracle Solaris Studio Performance Library                            dgtsv(3P)



NAME
       dgtsv  -  solve  the  equation  A*X=B, where A is an N-by-N tridiagonal
       matrix, by Gaussian elimination with partial pivoting


SYNOPSIS
       SUBROUTINE DGTSV(N, NRHS, LOW, D, UP, B, LDB, INFO)

       INTEGER N, NRHS, LDB, INFO
       DOUBLE PRECISION LOW(*), D(*), UP(*), B(LDB,*)

       SUBROUTINE DGTSV_64(N, NRHS, LOW, D, UP, B, LDB, INFO)

       INTEGER*8 N, NRHS, LDB, INFO
       DOUBLE PRECISION LOW(*), D(*), UP(*), B(LDB,*)




   F95 INTERFACE
       SUBROUTINE GTSV(N, NRHS, LOW, D, UP, B, LDB, INFO)

       INTEGER :: N, NRHS, LDB, INFO
       REAL(8), DIMENSION(:) :: LOW, D, UP
       REAL(8), DIMENSION(:,:) :: B

       SUBROUTINE GTSV_64(N, NRHS, LOW, D, UP, B, LDB, INFO)

       INTEGER(8) :: N, NRHS, LDB, INFO
       REAL(8), DIMENSION(:) :: LOW, D, UP
       REAL(8), DIMENSION(:,:) :: B




   C INTERFACE
       #include <sunperf.h>

       void dgtsv(int n, int nrhs, double *low, double *d, double *up,  double
                 *b, int ldb, int *info);

       void  dgtsv_64(long  n,  long nrhs, double *low, double *d, double *up,
                 double *b, long ldb, long *info);



PURPOSE
       dgtsv solves the equation A*X=B, where A  is  an  n  by  n  tridiagonal
       matrix, by Gaussian elimination with partial pivoting.

       Note that the equation A'*X=B  may be solved by interchanging the order
       of the arguments DU and DL.


ARGUMENTS
       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/output)
                 On entry, LOW must contain the (n-1) sub-diagonal elements of
                 A.

                 On exit, LOW is overwritten by the (n-2) elements of the sec-
                 ond  super-diagonal of the upper triangular matrix U from the
                 LU factorization of A, in LOW(1), ..., LOW(n-2).


       D (input/output)
                 On entry, D must contain the diagonal elements of A.

                 On exit, D is overwritten by the n diagonal elements of U.


       UP (input/output)
                 On entry, UP must contain the (n-1)  super-diagonal  elements
                 of A.

                 On exit, UP is overwritten by the (n-1) elements of the first
                 super-diagonal of U.


       B (input/output)
                 On entry, the N by NRHS matrix of right hand side  matrix  B.
                 On exit, if INFO = 0, the N by NRHS solution matrix X.


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


       INFO (output)
                 = 0: successful exit
                 < 0: if INFO = -i, the i-th argument had an illegal value
                 >  0:  if  INFO = i, U(i,i) is exactly zero, and the solution
                 has not been computed.  The factorization has not  been  com-
                 pleted unless i = N.




                                  7 Nov 2015                         dgtsv(3P)