Contents


NAME

     dgbcon - estimate the reciprocal of the condition number  of
     a  real  general  band matrix A, in either the 1-norm or the
     infinity-norm,

SYNOPSIS

     SUBROUTINE DGBCON(NORM, N, NSUB, NSUPER, A, LDA, IPIVOT, ANORM,
           RCOND, WORK, WORK2, INFO)

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

     SUBROUTINE DGBCON_64(NORM, N, NSUB, NSUPER, A, LDA, IPIVOT, ANORM,
           RCOND, WORK, WORK2, INFO)

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

  F95 INTERFACE
     SUBROUTINE GBCON(NORM, [N], NSUB, NSUPER, A, [LDA], IPIVOT, ANORM,
            RCOND, [WORK], [WORK2], [INFO])

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

     SUBROUTINE GBCON_64(NORM, [N], NSUB, NSUPER, A, [LDA], IPIVOT, ANORM,
            RCOND, [WORK], [WORK2], [INFO])

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

  C INTERFACE
     #include <sunperf.h>
     void dgbcon(char norm, int n, int nsub, int  nsuper,  double
               *a,  int  lda,  int  *ipivot, double anorm, double
               *rcond, int *info);

     void dgbcon_64(char norm, long n, long  nsub,  long  nsuper,
               double  *a,  long lda, long *ipivot, double anorm,
               double *rcond, long *info);

PURPOSE

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

     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 infinity-norm condition number is required:
               = '1' or 'O':  1-norm;
               = 'I':         Infinity-norm.

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

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

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

     A (input) Details of the LU factorization of the band matrix
               A, as computed by SGBTRF.  U is stored as an upper
               triangular band matrix with NSUB+NSUPER superdiag-
               onals  in  rows 1 to NSUB+NSUPER+1, and the multi-
               pliers used during the factorization are stored in
               rows NSUB+NSUPER+2 to 2*NSUB+NSUPER+1.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               2*NSUB+NSUPER+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,  computed  as  RCOND  =  1/(norm(A)  *
               norm(inv(A))).

     WORK (workspace)
               dimension(3*N)

     WORK2 (workspace)
               dimension (N)

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