Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zgbcon (3p)

Name

zgbcon - estimate the reciprocal of the condition number of a complex general band matrix A, in either the 1-norm or the infinity-norm, using the LU factorization computed by ZGBTRF

Synopsis

SUBROUTINE ZGBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)

CHARACTER*1 NORM
DOUBLE COMPLEX A(LDA,*), WORK(*)
INTEGER N, KL, KU, LDA, INFO
INTEGER IPIVOT(*)
DOUBLE PRECISION ANORM, RCOND
DOUBLE PRECISION WORK2(*)

SUBROUTINE ZGBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)

CHARACTER*1 NORM
DOUBLE COMPLEX A(LDA,*), WORK(*)
INTEGER*8 N, KL, KU, LDA, INFO
INTEGER*8 IPIVOT(*)
DOUBLE PRECISION ANORM, RCOND
DOUBLE PRECISION WORK2(*)




F95 INTERFACE
SUBROUTINE GBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)

CHARACTER(LEN=1) :: NORM
COMPLEX(8), DIMENSION(:) :: WORK
COMPLEX(8), DIMENSION(:,:) :: A
INTEGER :: N, KL, KU, LDA, INFO
INTEGER, DIMENSION(:) :: IPIVOT
REAL(8) :: ANORM, RCOND
REAL(8), DIMENSION(:) :: WORK2

SUBROUTINE GBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
RCOND, WORK, WORK2, INFO)

CHARACTER(LEN=1) :: NORM
COMPLEX(8), DIMENSION(:) :: WORK
COMPLEX(8), DIMENSION(:,:) :: A
INTEGER(8) :: N, KL, KU, LDA, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT
REAL(8) :: ANORM, RCOND
REAL(8), DIMENSION(:) :: WORK2




C INTERFACE
#include <sunperf.h>

void  zgbcon(char  norm,  int  n, int kl, int ku, doublecomplex *a, int
lda, int *ipivot, double anorm, double *rcond, int *info);

void zgbcon_64(char norm, long n, long kl, long ku,  doublecomplex  *a,
long  lda,  long  *ipivot,  double anorm, double *rcond, long
*info);

Description

Oracle Solaris Studio Performance Library                           zgbcon(3P)



NAME
       zgbcon  -  estimate the reciprocal of the condition number of a complex
       general band matrix A, in either the 1-norm or the infinity-norm, using
       the LU factorization computed by ZGBTRF


SYNOPSIS
       SUBROUTINE ZGBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
             RCOND, WORK, WORK2, INFO)

       CHARACTER*1 NORM
       DOUBLE COMPLEX A(LDA,*), WORK(*)
       INTEGER N, KL, KU, LDA, INFO
       INTEGER IPIVOT(*)
       DOUBLE PRECISION ANORM, RCOND
       DOUBLE PRECISION WORK2(*)

       SUBROUTINE ZGBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
             RCOND, WORK, WORK2, INFO)

       CHARACTER*1 NORM
       DOUBLE COMPLEX A(LDA,*), WORK(*)
       INTEGER*8 N, KL, KU, LDA, INFO
       INTEGER*8 IPIVOT(*)
       DOUBLE PRECISION ANORM, RCOND
       DOUBLE PRECISION WORK2(*)




   F95 INTERFACE
       SUBROUTINE GBCON(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
              RCOND, WORK, WORK2, INFO)

       CHARACTER(LEN=1) :: NORM
       COMPLEX(8), DIMENSION(:) :: WORK
       COMPLEX(8), DIMENSION(:,:) :: A
       INTEGER :: N, KL, KU, LDA, INFO
       INTEGER, DIMENSION(:) :: IPIVOT
       REAL(8) :: ANORM, RCOND
       REAL(8), DIMENSION(:) :: WORK2

       SUBROUTINE GBCON_64(NORM, N, KL, KU, A, LDA, IPIVOT, ANORM,
              RCOND, WORK, WORK2, INFO)

       CHARACTER(LEN=1) :: NORM
       COMPLEX(8), DIMENSION(:) :: WORK
       COMPLEX(8), DIMENSION(:,:) :: A
       INTEGER(8) :: N, KL, KU, LDA, INFO
       INTEGER(8), DIMENSION(:) :: IPIVOT
       REAL(8) :: ANORM, RCOND
       REAL(8), DIMENSION(:) :: WORK2




   C INTERFACE
       #include <sunperf.h>

       void  zgbcon(char  norm,  int  n, int kl, int ku, doublecomplex *a, int
                 lda, int *ipivot, double anorm, double *rcond, int *info);

       void zgbcon_64(char norm, long n, long kl, long ku,  doublecomplex  *a,
                 long  lda,  long  *ipivot,  double anorm, double *rcond, long
                 *info);



PURPOSE
       zgbcon estimates the reciprocal of the condition number  of  a  complex
       general band matrix A, in either the 1-norm or the infinity-norm, using
       the LU factorization computed by ZGBTRF.

       An estimate is obtained for norm(inv(A)), and  the  reciprocal  of  the
       condition number is computed as
          RCOND = 1 / ( norm(A) * 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.


       KL (input)
                 The number of subdiagonals within the band of A.  KL >= 0.


       KU (input)
                 The number of superdiagonals within the band of A.  KU >=  0.


       A (input) Details of the LU factorization of the band matrix A, as com-
                 puted by ZGBTRF.  U is stored as  an  upper  triangular  band
                 matrix  with  KL+KU  superdiagonals in rows 1 to KL+KU+1, and
                 the multipliers used during the factorization are  stored  in
                 rows KL+KU+2 to 2*KL+KU+1.


       LDA (input)
                 The leading dimension of the array A.  LDA >= 2*KL+KU+1.


       IPIVOT (input)
                 The  pivot  indices; for 1 <= i <= N, row i of the matrix was
                 interchanged with row IPIVOT(i).


       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/(norm(A) * norm(inv(A))).


       WORK (workspace)
                 dimension(2*N)

       WORK2 (workspace)
                 dimension (N)


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




                                  7 Nov 2015                        zgbcon(3P)