Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zpttrs (3p)

Name

zpttrs - 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 ZPTTRS(UPLO, N, NRHS, D, E, B, LDB, INFO)

CHARACTER*1 UPLO
DOUBLE COMPLEX E(*), B(LDB,*)
INTEGER N, NRHS, LDB, INFO
DOUBLE PRECISION D(*)

SUBROUTINE ZPTTRS_64(UPLO, N, NRHS, D, E, B, LDB, INFO)

CHARACTER*1 UPLO
DOUBLE COMPLEX E(*), B(LDB,*)
INTEGER*8 N, NRHS, LDB, INFO
DOUBLE PRECISION D(*)




F95 INTERFACE
SUBROUTINE PTTRS(UPLO, N, NRHS, D, E, B, LDB, INFO)

CHARACTER(LEN=1) :: UPLO
COMPLEX(8), DIMENSION(:) :: E
COMPLEX(8), DIMENSION(:,:) :: B
INTEGER :: N, NRHS, LDB, INFO
REAL(8), DIMENSION(:) :: D

SUBROUTINE PTTRS_64(UPLO, N, NRHS, D, E, B, LDB, INFO)

CHARACTER(LEN=1) :: UPLO
COMPLEX(8), DIMENSION(:) :: E
COMPLEX(8), DIMENSION(:,:) :: B
INTEGER(8) :: N, NRHS, LDB, INFO
REAL(8), DIMENSION(:) :: D




C INTERFACE
#include <sunperf.h>

void zpttrs(char uplo, int n, int nrhs, double  *d,  doublecomplex  *e,
doublecomplex *b, int ldb, int *info);

void  zpttrs_64(char  uplo, long n, long nrhs, double *d, doublecomplex
*e, doublecomplex *b, long ldb, long *info);

Description

Oracle Solaris Studio Performance Library                           zpttrs(3P)



NAME
       zpttrs  -  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 ZPTTRS(UPLO, N, NRHS, D, E, B, LDB, INFO)

       CHARACTER*1 UPLO
       DOUBLE COMPLEX E(*), B(LDB,*)
       INTEGER N, NRHS, LDB, INFO
       DOUBLE PRECISION D(*)

       SUBROUTINE ZPTTRS_64(UPLO, N, NRHS, D, E, B, LDB, INFO)

       CHARACTER*1 UPLO
       DOUBLE COMPLEX E(*), B(LDB,*)
       INTEGER*8 N, NRHS, LDB, INFO
       DOUBLE PRECISION D(*)




   F95 INTERFACE
       SUBROUTINE PTTRS(UPLO, N, NRHS, D, E, B, LDB, INFO)

       CHARACTER(LEN=1) :: UPLO
       COMPLEX(8), DIMENSION(:) :: E
       COMPLEX(8), DIMENSION(:,:) :: B
       INTEGER :: N, NRHS, LDB, INFO
       REAL(8), DIMENSION(:) :: D

       SUBROUTINE PTTRS_64(UPLO, N, NRHS, D, E, B, LDB, INFO)

       CHARACTER(LEN=1) :: UPLO
       COMPLEX(8), DIMENSION(:) :: E
       COMPLEX(8), DIMENSION(:,:) :: B
       INTEGER(8) :: N, NRHS, LDB, INFO
       REAL(8), DIMENSION(:) :: D




   C INTERFACE
       #include <sunperf.h>

       void zpttrs(char uplo, int n, int nrhs, double  *d,  doublecomplex  *e,
                 doublecomplex *b, int ldb, int *info);

       void  zpttrs_64(char  uplo, long n, long nrhs, double *d, doublecomplex
                 *e, doublecomplex *b, long ldb, long *info);



PURPOSE
       zpttrs 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
       UPLO (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.  = 'U':
                 A = U'*D*U, E is the superdiagonal of U
                 = 'L':  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 UPLO = 'U', the (n-1) superdiagonal elements of  the  unit
                 bidiagonal  factor  U  from the factorization A = U'*D*U.  If
                 UPLO = 'L', the (n-1) subdiagonal elements of the unit  bidi-
                 agonal 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).


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




                                  7 Nov 2015                        zpttrs(3P)