Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zptts2 (3p)

Name

zptts2 - solve a tridiagonal system of the form A * X = B using the factorization A = U'*D*U or A = L*D*L' computed by ZPTTRF

Synopsis

SUBROUTINE ZPTTS2(IUPLO, N, NRHS, D, E, B, LDB)

DOUBLE COMPLEX E(*), B(LDB,*)
INTEGER IUPLO, N, NRHS, LDB
DOUBLE PRECISION D(*)

SUBROUTINE ZPTTS2_64(IUPLO, N, NRHS, D, E, B, LDB)

DOUBLE COMPLEX E(*), B(LDB,*)
INTEGER*8 IUPLO, N, NRHS, LDB
DOUBLE PRECISION D(*)




F95 INTERFACE
SUBROUTINE ZPTTS2(IUPLO, N, NRHS, D, E, B, LDB)

COMPLEX(8), DIMENSION(:) :: E
COMPLEX(8), DIMENSION(:,:) :: B
INTEGER :: IUPLO, N, NRHS, LDB
REAL(8), DIMENSION(:) :: D

SUBROUTINE ZPTTS2_64(IUPLO, N, NRHS, D, E, B, LDB)

COMPLEX(8), DIMENSION(:) :: E
COMPLEX(8), DIMENSION(:,:) :: B
INTEGER(8) :: IUPLO, N, NRHS, LDB
REAL(8), DIMENSION(:) :: D




C INTERFACE
#include <sunperf.h>

void zptts2(int iuplo, int n, int nrhs, double  *d,  doublecomplex  *e,
doublecomplex *b, int ldb);

void  zptts2_64(long iuplo, long n, long nrhs, double *d, doublecomplex
*e, doublecomplex *b, long ldb);

Description

Oracle Solaris Studio Performance Library                           zptts2(3P)



NAME
       zptts2  -  solve  a tridiagonal system of the form  A * X = B using the
       factorization A = U'*D*U or A = L*D*L' computed by ZPTTRF


SYNOPSIS
       SUBROUTINE ZPTTS2(IUPLO, N, NRHS, D, E, B, LDB)

       DOUBLE COMPLEX E(*), B(LDB,*)
       INTEGER IUPLO, N, NRHS, LDB
       DOUBLE PRECISION D(*)

       SUBROUTINE ZPTTS2_64(IUPLO, N, NRHS, D, E, B, LDB)

       DOUBLE COMPLEX E(*), B(LDB,*)
       INTEGER*8 IUPLO, N, NRHS, LDB
       DOUBLE PRECISION D(*)




   F95 INTERFACE
       SUBROUTINE ZPTTS2(IUPLO, N, NRHS, D, E, B, LDB)

       COMPLEX(8), DIMENSION(:) :: E
       COMPLEX(8), DIMENSION(:,:) :: B
       INTEGER :: IUPLO, N, NRHS, LDB
       REAL(8), DIMENSION(:) :: D

       SUBROUTINE ZPTTS2_64(IUPLO, N, NRHS, D, E, B, LDB)

       COMPLEX(8), DIMENSION(:) :: E
       COMPLEX(8), DIMENSION(:,:) :: B
       INTEGER(8) :: IUPLO, N, NRHS, LDB
       REAL(8), DIMENSION(:) :: D




   C INTERFACE
       #include <sunperf.h>

       void zptts2(int iuplo, int n, int nrhs, double  *d,  doublecomplex  *e,
                 doublecomplex *b, int ldb);

       void  zptts2_64(long iuplo, long n, long nrhs, double *d, doublecomplex
                 *e, doublecomplex *b, long ldb);



PURPOSE
       zptts2 solves a tridiagonal system of the form
          A * X = B using the factorization A = U'*D*U or A = L*D*L'  computed
       by  ZPTTRF.  D is a diagonal matrix specified in the vector D, U (or L)
       is a unit bidiagonal matrix whose superdiagonal (subdiagonal) is speci-
       fied in the vector E, and X and B are N by NRHS matrices.


ARGUMENTS
       IUPLO (input)
                 Specifies  the form of the factorization and whether the vec-
                 tor E is the superdiagonal of the upper bidiagonal  factor  U
                 or the subdiagonal of the lower bidiagonal factor L.  = 1:  A
                 = U'*D*U, E is the superdiagonal of U
                 = 0:  A = L*D*L', E is the subdiagonal of L


       N (input) The order of the tridiagonal 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) The  n  diagonal  elements  of the diagonal matrix D from the
                 factorization A = U'*D*U or A = L*D*L'.


       E (input) If IUPLO = 1, the (n-1) superdiagonal elements  of  the  unit
                 bidiagonal  factor  U  from the factorization A = U'*D*U.  If
                 IUPLO = 0, the (n-1) subdiagonal elements of the unit bidiag-
                 onal factor L from the factorization A = L*D*L'.


       B (input/output)
                 On  entry,  the  right  hand side vectors B for the system of
                 linear equations.  On exit, the solution vectors, X.


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




                                  7 Nov 2015                        zptts2(3P)