dptsv - compute the solution to a real system of linear equations A*X = B, where A is an N-by-N symmetric positive definite tridiagonal matrix, and X and B are N-by-NRHS matrices
SUBROUTINE DPTSV(N, NRHS, D, E, B, LDB, INFO) INTEGER N, NRHS, LDB, INFO DOUBLE PRECISION D(*), E(*), B(LDB,*) SUBROUTINE DPTSV_64(N, NRHS, D, E, B, LDB, INFO) INTEGER*8 N, NRHS, LDB, INFO DOUBLE PRECISION D(*), E(*), B(LDB,*) F95 INTERFACE SUBROUTINE PTSV(N, NRHS, D, E, B, LDB, INFO) INTEGER :: N, NRHS, LDB, INFO REAL(8), DIMENSION(:) :: D, E REAL(8), DIMENSION(:,:) :: B SUBROUTINE PTSV_64(N, NRHS, D, E, B, LDB, INFO) INTEGER(8) :: N, NRHS, LDB, INFO REAL(8), DIMENSION(:) :: D, E REAL(8), DIMENSION(:,:) :: B C INTERFACE #include <sunperf.h> void dptsv(int n, int nrhs, double *d, double *e, double *b, int ldb, int *info); void dptsv_64(long n, long nrhs, double *d, double *e, double *b, long ldb, long *info);
Oracle Solaris Studio Performance Library dptsv(3P)
NAME
dptsv - compute the solution to a real system of linear equations A*X =
B, where A is an N-by-N symmetric positive definite tridiagonal matrix,
and X and B are N-by-NRHS matrices
SYNOPSIS
SUBROUTINE DPTSV(N, NRHS, D, E, B, LDB, INFO)
INTEGER N, NRHS, LDB, INFO
DOUBLE PRECISION D(*), E(*), B(LDB,*)
SUBROUTINE DPTSV_64(N, NRHS, D, E, B, LDB, INFO)
INTEGER*8 N, NRHS, LDB, INFO
DOUBLE PRECISION D(*), E(*), B(LDB,*)
F95 INTERFACE
SUBROUTINE PTSV(N, NRHS, D, E, B, LDB, INFO)
INTEGER :: N, NRHS, LDB, INFO
REAL(8), DIMENSION(:) :: D, E
REAL(8), DIMENSION(:,:) :: B
SUBROUTINE PTSV_64(N, NRHS, D, E, B, LDB, INFO)
INTEGER(8) :: N, NRHS, LDB, INFO
REAL(8), DIMENSION(:) :: D, E
REAL(8), DIMENSION(:,:) :: B
C INTERFACE
#include <sunperf.h>
void dptsv(int n, int nrhs, double *d, double *e, double *b, int ldb,
int *info);
void dptsv_64(long n, long nrhs, double *d, double *e, double *b, long
ldb, long *info);
PURPOSE
dptsv computes the solution to a real system of linear equations A*X =
B, where A is an N-by-N symmetric positive definite tridiagonal matrix,
and X and B are N-by-NRHS matrices.
A is factored as A = L*D*L**T, and the factored form of A is then used
to solve the system of equations.
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.
D (input/output)
On entry, the n diagonal elements of the tridiagonal matrix
A. On exit, the n diagonal elements of the diagonal matrix D
from the factorization A = L*D*L**T.
E (input/output)
On entry, the (n-1) subdiagonal elements of the tridiagonal
matrix A. On exit, the (n-1) subdiagonal elements of the
unit bidiagonal factor L from the L*D*L**T factorization of
A. (E can also be regarded as the superdiagonal of the unit
bidiagonal factor U from the U**T*D*U factorization of A.)
B (input/output)
On entry, the N-by-NRHS 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, the leading minor of order i is not posi-
tive definite, and the solution has not been computed. The
factorization has not been completed unless i = N.
7 Nov 2015 dptsv(3P)