Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgecon (3p)

Name

dgecon - estimate the reciprocal of the condition number of a general real matrix A, in either the 1-norm or the infinity-norm, using the LU factorization computed by DGETRF

Synopsis

SUBROUTINE DGECON(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2, INFO)

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

SUBROUTINE DGECON_64(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2,
INFO)

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




F95 INTERFACE
SUBROUTINE GECON(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2,
INFO)

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

SUBROUTINE GECON_64(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2,
INFO)

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




C INTERFACE
#include <sunperf.h>

void  dgecon(char norm, int n, double *a, int lda, double anorm, double
*rcond, int *info);

void dgecon_64(char norm, long n, double *a, long  lda,  double  anorm,
double *rcond, long *info);

Description

Oracle Solaris Studio Performance Library                           dgecon(3P)



NAME
       dgecon  -  estimate the reciprocal of the condition number of a general
       real matrix A, in either the 1-norm or the infinity-norm, using the  LU
       factorization computed by DGETRF


SYNOPSIS
       SUBROUTINE DGECON(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2, INFO)

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

       SUBROUTINE DGECON_64(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2,
             INFO)

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




   F95 INTERFACE
       SUBROUTINE GECON(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2,
              INFO)

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

       SUBROUTINE GECON_64(NORM, N, A, LDA, ANORM, RCOND, WORK, WORK2,
              INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void  dgecon(char norm, int n, double *a, int lda, double anorm, double
                 *rcond, int *info);

       void dgecon_64(char norm, long n, double *a, long  lda,  double  anorm,
                 double *rcond, long *info);



PURPOSE
       dgecon  estimates  the  reciprocal of the condition number of a general
       real matrix A, in either the 1-norm or the infinity-norm, using the  LU
       factorization computed by DGETRF.

       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.


       A (input) The  factors L and U from the factorization A = P*L*U as com-
                 puted by DGETRF.


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


       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(4*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                        dgecon(3P)