Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zgtcon (3p)

Name

zgtcon - estimate the reciprocal of the condition number of a complex tridiagonal matrix A using the LU factorization as computed by ZGTTRF

Synopsis

SUBROUTINE ZGTCON(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM, RCOND,
WORK, INFO)

CHARACTER*1 NORM
DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*), WORK(*)
INTEGER N, INFO
INTEGER IPIVOT(*)
DOUBLE PRECISION ANORM, RCOND

SUBROUTINE ZGTCON_64(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM,
RCOND, WORK, INFO)

CHARACTER*1 NORM
DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*), WORK(*)
INTEGER*8 N, INFO
INTEGER*8 IPIVOT(*)
DOUBLE PRECISION ANORM, RCOND




F95 INTERFACE
SUBROUTINE GTCON(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM,
RCOND, WORK, INFO)

CHARACTER(LEN=1) :: NORM
COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2, WORK
INTEGER :: N, INFO
INTEGER, DIMENSION(:) :: IPIVOT
REAL(8) :: ANORM, RCOND

SUBROUTINE GTCON_64(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM,
RCOND, WORK, INFO)

CHARACTER(LEN=1) :: NORM
COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2, WORK
INTEGER(8) :: N, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT
REAL(8) :: ANORM, RCOND




C INTERFACE
#include <sunperf.h>

void zgtcon(char norm, int n,  doublecomplex  *low,  doublecomplex  *d,
doublecomplex  *up1,  doublecomplex *up2, int *ipivot, double
anorm, double *rcond, int *info);

void zgtcon_64(char norm, long n, doublecomplex *low, doublecomplex *d,
doublecomplex  *up1, doublecomplex *up2, long *ipivot, double
anorm, double *rcond, long *info);

Description

Oracle Solaris Studio Performance Library                           zgtcon(3P)



NAME
       zgtcon  -  estimate the reciprocal of the condition number of a complex
       tridiagonal matrix A using the LU factorization as computed by ZGTTRF


SYNOPSIS
       SUBROUTINE ZGTCON(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM, RCOND,
             WORK, INFO)

       CHARACTER*1 NORM
       DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*), WORK(*)
       INTEGER N, INFO
       INTEGER IPIVOT(*)
       DOUBLE PRECISION ANORM, RCOND

       SUBROUTINE ZGTCON_64(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM,
             RCOND, WORK, INFO)

       CHARACTER*1 NORM
       DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*), WORK(*)
       INTEGER*8 N, INFO
       INTEGER*8 IPIVOT(*)
       DOUBLE PRECISION ANORM, RCOND




   F95 INTERFACE
       SUBROUTINE GTCON(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM,
              RCOND, WORK, INFO)

       CHARACTER(LEN=1) :: NORM
       COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2, WORK
       INTEGER :: N, INFO
       INTEGER, DIMENSION(:) :: IPIVOT
       REAL(8) :: ANORM, RCOND

       SUBROUTINE GTCON_64(NORM, N, LOW, D, UP1, UP2, IPIVOT, ANORM,
              RCOND, WORK, INFO)

       CHARACTER(LEN=1) :: NORM
       COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2, WORK
       INTEGER(8) :: N, INFO
       INTEGER(8), DIMENSION(:) :: IPIVOT
       REAL(8) :: ANORM, RCOND




   C INTERFACE
       #include <sunperf.h>

       void zgtcon(char norm, int n,  doublecomplex  *low,  doublecomplex  *d,
                 doublecomplex  *up1,  doublecomplex *up2, int *ipivot, double
                 anorm, double *rcond, int *info);

       void zgtcon_64(char norm, long n, doublecomplex *low, doublecomplex *d,
                 doublecomplex  *up1, doublecomplex *up2, long *ipivot, double
                 anorm, double *rcond, long *info);



PURPOSE
       zgtcon estimates the reciprocal of the condition number  of  a  complex
       tridiagonal  matrix A using the LU factorization as computed by ZGTTRF.

       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
       NORM (input)
                 Specifies  whether  the 1-norm condition number or the infin-
                 ity-norm condition number is required:
                 = '1' or 'O':  1-norm;
                 = 'I':         Infinity-norm.


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


       LOW (input)
                 The (n-1) multipliers that define the matrix L  from  the  LU
                 factorization of A as computed by ZGTTRF.


       D (input) The n diagonal elements of the upper triangular matrix U from
                 the LU factorization of A.


       UP1 (input)
                 The (n-1) elements of the first superdiagonal of U.


       UP2 (input)
                 The (n-2) elements of the second superdiagonal of U.


       IPIVOT (input)
                 The pivot indices; for 1 <= i <= n, row i of the  matrix  was
                 interchanged  with  row  IPIVOT(i).  IPIVOT(i) will always be
                 either i or i+1; IPIVOT(i) = i indicates  a  row  interchange
                 was not required.


       ANORM (input)
                 If  NORM  =  '1' or 'O', the 1-norm of the original matrix A.
                 If NORM = 'I', the infinity-norm of the original 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)
                 dimension(2*N)

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




                                  7 Nov 2015                        zgtcon(3P)