Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sstsv (3p)

Name

sstsv - compute the solution to a system of linear equations A * X = B where A is a symmetric tridiagonal matrix

Synopsis

SUBROUTINE SSTSV(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

INTEGER N, NRHS, LDB, INFO
INTEGER IPIV(*)
REAL L(*), D(*), SUBL(*), B(LDB,*)

SUBROUTINE SSTSV_64(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

INTEGER*8 N, NRHS, LDB, INFO
INTEGER*8 IPIV(*)
REAL L(*), D(*), SUBL(*), B(LDB,*)




F95 INTERFACE
SUBROUTINE STSV(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

INTEGER :: N, NRHS, LDB, INFO
INTEGER, DIMENSION(:) :: IPIV
REAL, DIMENSION(:) :: L, D, SUBL
REAL, DIMENSION(:,:) :: B

SUBROUTINE STSV_64(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

INTEGER(8) :: N, NRHS, LDB, INFO
INTEGER(8), DIMENSION(:) :: IPIV
REAL, DIMENSION(:) :: L, D, SUBL
REAL, DIMENSION(:,:) :: B




C INTERFACE
#include <sunperf.h>

void sstsv(int n, int nrhs, float *l, float *d, float *subl, float  *b,
int ldb, int *ipiv, int *info);

void sstsv_64(long n, long nrhs, float *l, float *d, float *subl, float
*b, long ldb, long *ipiv, long *info);

Description

Oracle Solaris Studio Performance Library                            sstsv(3P)



NAME
       sstsv  - compute the solution to a system of linear equations A * X = B
       where A is a symmetric tridiagonal matrix


SYNOPSIS
       SUBROUTINE SSTSV(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

       INTEGER N, NRHS, LDB, INFO
       INTEGER IPIV(*)
       REAL L(*), D(*), SUBL(*), B(LDB,*)

       SUBROUTINE SSTSV_64(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

       INTEGER*8 N, NRHS, LDB, INFO
       INTEGER*8 IPIV(*)
       REAL L(*), D(*), SUBL(*), B(LDB,*)




   F95 INTERFACE
       SUBROUTINE STSV(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

       INTEGER :: N, NRHS, LDB, INFO
       INTEGER, DIMENSION(:) :: IPIV
       REAL, DIMENSION(:) :: L, D, SUBL
       REAL, DIMENSION(:,:) :: B

       SUBROUTINE STSV_64(N, NRHS, L, D, SUBL, B, LDB, IPIV, INFO)

       INTEGER(8) :: N, NRHS, LDB, INFO
       INTEGER(8), DIMENSION(:) :: IPIV
       REAL, DIMENSION(:) :: L, D, SUBL
       REAL, DIMENSION(:,:) :: B




   C INTERFACE
       #include <sunperf.h>

       void sstsv(int n, int nrhs, float *l, float *d, float *subl, float  *b,
                 int ldb, int *ipiv, int *info);

       void sstsv_64(long n, long nrhs, float *l, float *d, float *subl, float
                 *b, long ldb, long *ipiv, long *info);



PURPOSE
       sstsv computes the solution to a system of linear equations A * X  =  B
       where A is a symmetric tridiagonal matrix.


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


       NRHS (input)
                 The number of right hand sides in B.


       L (input/output)
                  REAL array, dimension (N-1)
                 On  entry,  the  n-1  subdiagonal elements of the tridiagonal
                 matrix A.  On exit, part of the factorization of A.


       D (input/output)
                  REAL array, dimension (N)
                 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 of A.


       SUBL (output)
                  REAL array, dimension (N-2)
                 On exit, part of the factorization of A.


       B (input/output)
                 The columns of B contain the right hand sides.


       LDB (input)
                 The leading dimension of B as specified in a type  or  DIMEN-
                 SION statement.


       IPIV (output)
                  INTEGER array, dimension (N)
                 On exit, the pivot indices of the factorization.


       INFO (output)
                  INTEGER
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  if INFO = i, D(k,k) is exactly zero.  The factorization
                 has been completed,  but  the  block  diagonal  matrix  D  is
                 exactly  singular  and  division  by zero will occur if it is
                 used to solve a system of equations.




                                  7 Nov 2015                         sstsv(3P)