Contents


NAME

     dtbcon - estimate the reciprocal of the condition number  of
     a  triangular  band  matrix  A,  in either the 1-norm or the
     infinity-norm

SYNOPSIS

     SUBROUTINE DTBCON(NORM, UPLO, DIAG, N, KD, A, LDA, RCOND, WORK,
           WORK2, INFO)

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

     SUBROUTINE DTBCON_64(NORM, UPLO, DIAG, N, KD, A, LDA, RCOND, WORK,
           WORK2, INFO)

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

  F95 INTERFACE
     SUBROUTINE TBCON(NORM, UPLO, DIAG, [N], KD, A, [LDA], RCOND, [WORK],
            [WORK2], [INFO])

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

     SUBROUTINE TBCON_64(NORM, UPLO, DIAG, [N], KD, A, [LDA], RCOND,
            [WORK], [WORK2], [INFO])

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

  C INTERFACE
     #include <sunperf.h>
     void dtbcon(char norm, char uplo, char diag, int n, int  kd,
               double *a, int lda, double *rcond, int *info);

     void dtbcon_64(char norm, char uplo, char diag, long n, long
               kd,  double  *a,  long  lda,  double  *rcond, long
               *info);

PURPOSE

     dtbcon estimates the reciprocal of the condition number of a
     triangular  band  matrix  A,  in  either  the  1-norm or the
     infinity-norm.

     The norm of A is computed and an estimate  is  obtained  for
     norm(inv(A)), then 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.

     UPLO (input)
               = 'U':  A is upper triangular;
               = 'L':  A is lower triangular.

     DIAG (input)
               = 'N':  A is non-unit triangular;
               = 'U':  A is unit triangular.

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

     KD (input)
               The number of superdiagonals  or  subdiagonals  of
               the triangular band matrix A.  KD >= 0.

     A (input) The upper  or  lower  triangular  band  matrix  A,
               stored  in  the  first kd+1 rows of the array. The
               j-th column of A is stored in the j-th  column  of
               the  array A as follows:  if UPLO = 'U', A(kd+1+i-
               j,j) = A(i,j) for  max(1,j-kd)<=i<=j;  if  UPLO  =
               'L', A(1+i-j,j)    = A(i,j) for j<=i<=min(n,j+kd).
               If DIAG = 'U', the diagonal elements of A are  not
               referenced and are assumed to be 1.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               KD+1.

     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