Contents


NAME

     dpbequ - compute row and column scalings intended to equili-
     brate a symmetric positive definite band matrix A and reduce
     its condition number (with respect to the two-norm)

SYNOPSIS

     SUBROUTINE DPBEQU(UPLO, N, KD, A, LDA, SCALE, SCOND, AMAX, INFO)

     CHARACTER * 1 UPLO
     INTEGER N, KD, LDA, INFO
     DOUBLE PRECISION SCOND, AMAX
     DOUBLE PRECISION A(LDA,*), SCALE(*)

     SUBROUTINE DPBEQU_64(UPLO, N, KD, A, LDA, SCALE, SCOND, AMAX,
           INFO)

     CHARACTER * 1 UPLO
     INTEGER*8 N, KD, LDA, INFO
     DOUBLE PRECISION SCOND, AMAX
     DOUBLE PRECISION A(LDA,*), SCALE(*)

  F95 INTERFACE
     SUBROUTINE PBEQU(UPLO, [N], KD, A, [LDA], SCALE, SCOND, AMAX,
            [INFO])

     CHARACTER(LEN=1) :: UPLO
     INTEGER :: N, KD, LDA, INFO
     REAL(8) :: SCOND, AMAX
     REAL(8), DIMENSION(:) :: SCALE
     REAL(8), DIMENSION(:,:) :: A

     SUBROUTINE PBEQU_64(UPLO, [N], KD, A, [LDA], SCALE, SCOND, AMAX,
            [INFO])

     CHARACTER(LEN=1) :: UPLO
     INTEGER(8) :: N, KD, LDA, INFO
     REAL(8) :: SCOND, AMAX
     REAL(8), DIMENSION(:) :: SCALE
     REAL(8), DIMENSION(:,:) :: A

  C INTERFACE
     #include <sunperf.h>

     void dpbequ(char uplo, int n, int kd, double  *a,  int  lda,
               double  *scale,  double  *scond, double *amax, int
               *info);
     void dpbequ_64(char uplo, long n, long kd, double  *a,  long
               lda,  double  *scale, double *scond, double *amax,
               long *info);

PURPOSE

     dpbequ computes row and column scalings intended to  equili-
     brate a symmetric positive definite band matrix A and reduce
     its condition number (with respect to the two-norm).  S con-
     tains  the  scale  factors, S(i) = 1/sqrt(A(i,i)), chosen so
     that  the  scaled  matrix   B   with   elements   B(i,j)   =
     S(i)*A(i,j)*S(j) has ones on the diagonal.  This choice of S
     puts the condition number of B within  a  factor  N  of  the
     smallest  possible condition number over all possible diago-
     nal scalings.

ARGUMENTS

     UPLO (input)
               = 'U':  Upper triangular of A is stored;
               = 'L':  Lower triangular of A is stored.

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

     KD (input)
               The number of superdiagonals of the  matrix  A  if
               UPLO  = 'U', or the number of subdiagonals if UPLO
               = 'L'.  KD >= 0.

     A (input) The upper or lower triangle of the symmetric  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).

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

     SCALE (output)
               If INFO = 0, SCALE contains the scale factors  for
               A.
     SCOND (output)
               If INFO = 0, SCALE contains the ratio of the smal-
               lest  SCALE(i)  to the largest SCALE(i).  If SCOND
               >= 0.1 and AMAX  is  neither  too  large  nor  too
               small, it is not worth scaling by SCALE.

     AMAX (output)
               Absolute value of largest matrix element.  If AMAX
               is  very close to overflow or very close to under-
               flow, the matrix should be scaled.

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               > 0:  if INFO = i, the i-th  diagonal  element  is
               nonpositive.