Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dsttrs (3p)

Name

dsttrs - compute 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

Synopsis

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,*)




F95 INTERFACE
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




C INTERFACE
#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);

Description

Oracle Solaris Studio Performance Library                           dsttrs(3P)



NAME
       dsttrs  - compute 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


SYNOPSIS
       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,*)




   F95 INTERFACE
       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




   C INTERFACE
       #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);



PURPOSE
       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.


ARGUMENTS
       N (input)
                  INTEGER
                 The order of the matrix A.  N >= 0.


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


       L (input)
                  REAL array, dimension (N-1)
                 On entry, the subdiagonal elements of L.


       D (input)
                  REAL array, dimension (N)
                 On entry, the diagonal elements of D.


       SUBL (input)
                  REAL array, dimension (N-2)
                 On entry, the second subdiagonal elements of L.


       B (input/output)
                  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.


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


       IPIV (input)
                 INTEGER array, dimension (N)
                 Details of the interchanges and block pivot. IPIV is provided
                 by DSTTRF. 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.


       INFO (output)
                  INTEGER
                 = 0:  successful exit
                 < 0:  if INFO = -k, the k-th argument had an illegal value




                                  7 Nov 2015                        dsttrs(3P)