Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zppcon (3p)

Name

zppcon - estimate the reciprocal of the condition number (in the 1-norm) of a complex Hermitian positive definite packed matrix using the Cholesky factorization A = U**H*U or A = L*L**H computed by ZPPTRF

Synopsis

SUBROUTINE ZPPCON(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

CHARACTER*1 UPLO
DOUBLE COMPLEX A(*), WORK(*)
INTEGER N, INFO
DOUBLE PRECISION ANORM, RCOND
DOUBLE PRECISION WORK2(*)

SUBROUTINE ZPPCON_64(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

CHARACTER*1 UPLO
DOUBLE COMPLEX A(*), WORK(*)
INTEGER*8 N, INFO
DOUBLE PRECISION ANORM, RCOND
DOUBLE PRECISION WORK2(*)




F95 INTERFACE
SUBROUTINE PPCON(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

CHARACTER(LEN=1) :: UPLO
COMPLEX(8), DIMENSION(:) :: A, WORK
INTEGER :: N, INFO
REAL(8) :: ANORM, RCOND
REAL(8), DIMENSION(:) :: WORK2

SUBROUTINE PPCON_64(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

CHARACTER(LEN=1) :: UPLO
COMPLEX(8), DIMENSION(:) :: A, WORK
INTEGER(8) :: N, INFO
REAL(8) :: ANORM, RCOND
REAL(8), DIMENSION(:) :: WORK2




C INTERFACE
#include <sunperf.h>

void  zppcon(char  uplo,  int n, doublecomplex *a, double anorm, double
*rcond, int *info);

void zppcon_64(char uplo, long n, doublecomplex *a, double anorm,  dou-
ble *rcond, long *info);

Description

Oracle Solaris Studio Performance Library                           zppcon(3P)



NAME
       zppcon  -  estimate  the  reciprocal  of  the  condition number (in the
       1-norm) of a complex Hermitian positive definite  packed  matrix  using
       the Cholesky factorization A = U**H*U or A = L*L**H computed by ZPPTRF


SYNOPSIS
       SUBROUTINE ZPPCON(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

       CHARACTER*1 UPLO
       DOUBLE COMPLEX A(*), WORK(*)
       INTEGER N, INFO
       DOUBLE PRECISION ANORM, RCOND
       DOUBLE PRECISION WORK2(*)

       SUBROUTINE ZPPCON_64(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

       CHARACTER*1 UPLO
       DOUBLE COMPLEX A(*), WORK(*)
       INTEGER*8 N, INFO
       DOUBLE PRECISION ANORM, RCOND
       DOUBLE PRECISION WORK2(*)




   F95 INTERFACE
       SUBROUTINE PPCON(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

       CHARACTER(LEN=1) :: UPLO
       COMPLEX(8), DIMENSION(:) :: A, WORK
       INTEGER :: N, INFO
       REAL(8) :: ANORM, RCOND
       REAL(8), DIMENSION(:) :: WORK2

       SUBROUTINE PPCON_64(UPLO, N, A, ANORM, RCOND, WORK, WORK2, INFO)

       CHARACTER(LEN=1) :: UPLO
       COMPLEX(8), DIMENSION(:) :: A, WORK
       INTEGER(8) :: N, INFO
       REAL(8) :: ANORM, RCOND
       REAL(8), DIMENSION(:) :: WORK2




   C INTERFACE
       #include <sunperf.h>

       void  zppcon(char  uplo,  int n, doublecomplex *a, double anorm, double
                 *rcond, int *info);

       void zppcon_64(char uplo, long n, doublecomplex *a, double anorm,  dou-
                 ble *rcond, long *info);



PURPOSE
       zppcon estimates the reciprocal of the condition number (in the 1-norm)
       of a complex  Hermitian  positive  definite  packed  matrix  using  the
       Cholesky factorization A = U**H*U or A = L*L**H computed by ZPPTRF.

       An  estimate  is  obtained  for norm(inv(A)), and the reciprocal of the
       condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).


ARGUMENTS
       UPLO (input)
                 = 'U':  Upper triangle of A is stored;
                 = 'L':  Lower triangle of A is stored.


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


       A (input) COMPLEX*16 array, dimension (N*(N+1)/2)
                 The triangular factor U or L from the Cholesky  factorization
                 A  =  U**H*U  or  A  =  L*L**H, packed columnwise in a linear
                 array.  The j-th column of U or L is stored in the array A as
                 follows:  if  UPLO  =  'U',  A(i  +  (j-1)*j/2)  = U(i,j) for
                 1<=i<=j; if UPLO = 'L', A(i + (j-1)*(2n-j)/2)  =  L(i,j)  for
                 j<=i<=n.


       ANORM (input)
                 The 1-norm (or infinity-norm) of the Hermitian matrix A.


       RCOND (output)
                 The  reciprocal of the condition number of the matrix A, com-
                 puted as RCOND = 1/(ANORM * AINVNM), where AINVNM is an esti-
                 mate of the 1-norm of inv(A) computed in this routine.


       WORK (workspace)
                 COMPLEX*16 array, dimension(2*N)

       WORK2 (workspace)
                 DOUBLE PRECISION array, dimension(N)


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




                                  7 Nov 2015                        zppcon(3P)