dsttrs - computes the solution to a real system of linear equations A * X = B
SUBROUTINE DSTTRS( N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO) INTEGER N, NRHS, LDB, INFO INTEGER IPIV(*) DOUBLE PRECISION L(*), D(*), SUBL(*), B(LDB,*)
SUBROUTINE DSTTRS_64( N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO) INTEGER*8 N, NRHS, LDB, INFO INTEGER*8 IPIV(*) DOUBLE PRECISION L(*), D(*), SUBL(*), B(LDB,*)
SUBROUTINE STTRS( [N], [NRHS], L, D, SUBL, B, [LDB], IPIV, [INFO]) INTEGER :: N, NRHS, LDB, INFO INTEGER, DIMENSION(:) :: IPIV REAL(8), DIMENSION(:) :: L, D, SUBL REAL(8), DIMENSION(:,:) :: B
SUBROUTINE STTRS_64( [N], [NRHS], L, D, SUBL, B, [LDB], IPIV, [INFO]) INTEGER(8) :: N, NRHS, LDB, INFO INTEGER(8), DIMENSION(:) :: IPIV REAL(8), DIMENSION(:) :: L, D, SUBL REAL(8), DIMENSION(:,:) :: B
#include <sunperf.h>
void dsttrs(int n, int nrhs, double *l, double *d, double *subl, double *b, int ldb, int *ipiv, int *info);
void dsttrs_64(long n, long nrhs, double *l, double *d, double *subl, double *b, long ldb, long *ipiv, long *info);
dsttrs computes the solution to a real system of linear equations A * X = B, where A is an N-by-N symmetric tridiagonal matrix and X and B are N-by-NRHS matrices.
INTEGER
The order of the matrix A. N > = 0.
INTEGER
The number of right hand sides, i.e., the number of columns of the matrix B. NRHS > = 0.
REAL array, dimension (N-1)
On entry, the subdiagonal elements of LL and DD.
REAL array, dimension (N)
On entry, the diagonal elements of DD.
REAL array, dimension (N-2)
On entry, the second subdiagonal elements of LL.
REAL array, dimension
(LDB, NRHS) On entry, the N-by-NRHS right hand side matrix B. On exit, if INFO = 0, the N-by-NRHS solution matrix X.
INTEGER
The leading dimension of the array B. LDB > = max(1, N)
INTEGER array, dimension (N)
Details of the interchanges and block pivot. If IPIV(K)
> 0,
1 by 1 pivot, and if IPIV(K)
= K + 1 an interchange done; If
IPIV(K)
< 0, 2 by 2 pivot, no interchange required.
INTEGER
= 0: successful exit
< 0: if INFO = -k, the k-th argument had an illegal value