Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cptsvx (3p)

Name

cptsvx - use the factorization A = L*D*L**H to compute the solution to a complex system of linear equations A*X = B, where A is an N-by-N Her- mitian positive definite tridiagonal matrix and X and B are N-by-NRHS matrices

Synopsis

SUBROUTINE CPTSVX(FACT, N, NRHS, D, E, DF, EF, B, LDB, X,
LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

CHARACTER*1 FACT
COMPLEX E(*), EF(*), B(LDB,*), X(LDX,*), WORK(*)
INTEGER N, NRHS, LDB, LDX, INFO
REAL RCOND
REAL D(*), DF(*), FERR(*), BERR(*), WORK2(*)

SUBROUTINE CPTSVX_64(FACT, N, NRHS, D, E, DF, EF, B, LDB,
X, LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

CHARACTER*1 FACT
COMPLEX E(*), EF(*), B(LDB,*), X(LDX,*), WORK(*)
INTEGER*8 N, NRHS, LDB, LDX, INFO
REAL RCOND
REAL D(*), DF(*), FERR(*), BERR(*), WORK2(*)




F95 INTERFACE
SUBROUTINE PTSVX(FACT, N, NRHS, D, E, DF, EF, B, LDB,
X, LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

CHARACTER(LEN=1) :: FACT
COMPLEX, DIMENSION(:) :: E, EF, WORK
COMPLEX, DIMENSION(:,:) :: B, X
INTEGER :: N, NRHS, LDB, LDX, INFO
REAL :: RCOND
REAL, DIMENSION(:) :: D, DF, FERR, BERR, WORK2

SUBROUTINE PTSVX_64(FACT, N, NRHS, D, E, DF, EF, B,
LDB, X, LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

CHARACTER(LEN=1) :: FACT
COMPLEX, DIMENSION(:) :: E, EF, WORK
COMPLEX, DIMENSION(:,:) :: B, X
INTEGER(8) :: N, NRHS, LDB, LDX, INFO
REAL :: RCOND
REAL, DIMENSION(:) :: D, DF, FERR, BERR, WORK2




C INTERFACE
#include <sunperf.h>

void cptsvx(char fact, int n, int nrhs, float  *d,  complex  *e,  float
*df,  complex  *ef, complex *b, int ldb, complex *x, int ldx,
float *rcond, float *ferr, float *berr, int *info);

void cptsvx_64(char fact, long n, long  nrhs,  float  *d,  complex  *e,
float  *df,  complex  *ef,  complex *b, long ldb, complex *x,
long ldx,  float  *rcond,  float  *ferr,  float  *berr,  long
*info);

Description

Oracle Solaris Studio Performance Library                           cptsvx(3P)



NAME
       cptsvx  - use the factorization A = L*D*L**H to compute the solution to
       a complex system of linear equations A*X = B, where A is an N-by-N Her-
       mitian  positive  definite tridiagonal matrix and X and B are N-by-NRHS
       matrices


SYNOPSIS
       SUBROUTINE CPTSVX(FACT, N, NRHS, D, E, DF, EF, B, LDB, X,
             LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

       CHARACTER*1 FACT
       COMPLEX E(*), EF(*), B(LDB,*), X(LDX,*), WORK(*)
       INTEGER N, NRHS, LDB, LDX, INFO
       REAL RCOND
       REAL D(*), DF(*), FERR(*), BERR(*), WORK2(*)

       SUBROUTINE CPTSVX_64(FACT, N, NRHS, D, E, DF, EF, B, LDB,
             X, LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

       CHARACTER*1 FACT
       COMPLEX E(*), EF(*), B(LDB,*), X(LDX,*), WORK(*)
       INTEGER*8 N, NRHS, LDB, LDX, INFO
       REAL RCOND
       REAL D(*), DF(*), FERR(*), BERR(*), WORK2(*)




   F95 INTERFACE
       SUBROUTINE PTSVX(FACT, N, NRHS, D, E, DF, EF, B, LDB,
              X, LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

       CHARACTER(LEN=1) :: FACT
       COMPLEX, DIMENSION(:) :: E, EF, WORK
       COMPLEX, DIMENSION(:,:) :: B, X
       INTEGER :: N, NRHS, LDB, LDX, INFO
       REAL :: RCOND
       REAL, DIMENSION(:) :: D, DF, FERR, BERR, WORK2

       SUBROUTINE PTSVX_64(FACT, N, NRHS, D, E, DF, EF, B,
              LDB, X, LDX, RCOND, FERR, BERR, WORK, WORK2, INFO)

       CHARACTER(LEN=1) :: FACT
       COMPLEX, DIMENSION(:) :: E, EF, WORK
       COMPLEX, DIMENSION(:,:) :: B, X
       INTEGER(8) :: N, NRHS, LDB, LDX, INFO
       REAL :: RCOND
       REAL, DIMENSION(:) :: D, DF, FERR, BERR, WORK2




   C INTERFACE
       #include <sunperf.h>

       void cptsvx(char fact, int n, int nrhs, float  *d,  complex  *e,  float
                 *df,  complex  *ef, complex *b, int ldb, complex *x, int ldx,
                 float *rcond, float *ferr, float *berr, int *info);

       void cptsvx_64(char fact, long n, long  nrhs,  float  *d,  complex  *e,
                 float  *df,  complex  *ef,  complex *b, long ldb, complex *x,
                 long ldx,  float  *rcond,  float  *ferr,  float  *berr,  long
                 *info);



PURPOSE
       cptsvx uses the factorization A = L*D*L**H to compute the solution to a
       complex system of linear equations A*X = B, where A is an N-by-N Hermi-
       tian  positive  definite  tridiagonal  matrix and X and B are N-by-NRHS
       matrices.

       Error bounds on the solution and a condition  estimate  are  also  pro-
       vided.

       The following steps are performed:

       1. If FACT = 'N', the matrix A is factored as A = L*D*L**H, where L
          is a unit lower bidiagonal matrix and D is diagonal.  The
          factorization can also be regarded as having the form
          A = U**H*D*U.

       2. If the leading i-by-i principal minor is not positive definite,
          then the routine returns with INFO = i. Otherwise, the factored
          form of A is used to estimate the condition number of the matrix
          A.  If the reciprocal of the condition number is less than machine
          precision, INFO = N+1 is returned as a warning, but the routine
          still goes on to solve for X and compute error bounds as
          described below.

       3. The system of equations is solved for X using the factored form
          of A.

       4. Iterative refinement is applied to improve the computed solution
          matrix and calculate error bounds and backward error estimates
          for it.


ARGUMENTS
       FACT (input)
                 Specifies whether or not the factored form of the matrix A is
                 supplied on entry.  = 'F':  On entry, DF and EF  contain  the
                 factored  form  of A.  D, E, DF, and EF will not be modified.
                 = 'N':  The matrix A will be copied to DF  and  EF  and  fac-
                 tored.


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


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


       D (input) The n diagonal elements of the tridiagonal matrix A.


       E (input) The (n-1) subdiagonal elements of the tridiagonal matrix A.


       DF (input or output)
                 If FACT = 'F', then DF is an input argument and on entry con-
                 tains  the  n diagonal elements of the diagonal matrix D from
                 the L*D*L**H factorization of A.  If FACT = 'N', then  DF  is
                 an  output  argument and on exit contains the n diagonal ele-
                 ments of the diagonal matrix D from the  L*D*L**H  factoriza-
                 tion of A.


       EF (input or output)
                 If FACT = 'F', then EF is an input argument and on entry con-
                 tains the (n-1) subdiagonal elements of the  unit  bidiagonal
                 factor  L  from  the  L*D*L**H factorization of A.  If FACT =
                 'N', then EF is an output argument and on exit  contains  the
                 (n-1)  subdiagonal  elements  of the unit bidiagonal factor L
                 from the L*D*L**H factorization of A.


       B (input) The N-by-NRHS right hand side matrix B.


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


       X (output)
                 If INFO = 0 or INFO = N+1, the N-by-NRHS solution matrix X.


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


       RCOND (output)
                 The reciprocal condition number of the matrix A.  If RCOND is
                 less  than  the  machine precision (in particular, if RCOND =
                 0), the matrix is singular to working precision.  This condi-
                 tion is indicated by a return code of INFO > 0.


       FERR (output)
                 The forward error bound for each solution vector X(j) (the j-
                 th column of the solution matrix X).  If XTRUE  is  the  true
                 solution corresponding to X(j), FERR(j) is an estimated upper
                 bound for the magnitude of the largest  element  in  (X(j)  -
                 XTRUE)  divided  by  the  magnitude of the largest element in
                 X(j).


       BERR (output)
                 The componentwise relative backward error  of  each  solution
                 vector  X(j)  (i.e., the smallest relative change in any ele-
                 ment of A or B that makes X(j) an exact solution).


       WORK (workspace)
                 dimension(N)

       WORK2 (workspace)
                 dimension(N)

       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  if INFO = i, and i is
                 <= N:  the leading minor of order i of A is not positive def-
                 inite,  so  the factorization could not be completed, and the
                 solution has not been computed. RCOND =  0  is  returned.   =
                 N+1:  U is nonsingular, but RCOND is less than machine preci-
                 sion, meaning that the matrix is singular to  working  preci-
                 sion.   Nevertheless,  the solution and error bounds are com-
                 puted because there are a number of situations where the com-
                 puted  solution  can be more accurate than the value of RCOND
                 would suggest.




                                  7 Nov 2015                        cptsvx(3P)