Contents


NAME

     zgbequ - compute row and column scalings intended to equili-
     brate  an  M-by-N  band  matrix  A  and reduce its condition
     number

SYNOPSIS

     SUBROUTINE ZGBEQU(M, N, KL, KU, A, LDA, R, C, ROWCN,
           COLCN, AMAX, INFO)

     DOUBLE COMPLEX A(LDA,*)
     INTEGER M, N, KL, KU, LDA, INFO
     DOUBLE PRECISION ROWCN, COLCN, AMAX
     DOUBLE PRECISION R(*), C(*)

     SUBROUTINE ZGBEQU_64(M, N, KL, KU, A, LDA, R, C, ROWCN,
           COLCN, AMAX, INFO)

     DOUBLE COMPLEX A(LDA,*)
     INTEGER*8 M, N, KL, KU, LDA, INFO
     DOUBLE PRECISION ROWCN, COLCN, AMAX
     DOUBLE PRECISION R(*), C(*)

  F95 INTERFACE
     SUBROUTINE GBEQU([M], [N], KL, KU, A, [LDA], R, C,
            ROWCN, COLCN, AMAX, [INFO])

     COMPLEX(8), DIMENSION(:,:) :: A
     INTEGER :: M, N, KL, KU, LDA, INFO
     REAL(8) :: ROWCN, COLCN, AMAX
     REAL(8), DIMENSION(:) :: R, C

     SUBROUTINE GBEQU_64([M], [N], KL, KU, A, [LDA], R, C,
            ROWCN, COLCN, AMAX, [INFO])

     COMPLEX(8), DIMENSION(:,:) :: A
     INTEGER(8) :: M, N, KL, KU, LDA, INFO
     REAL(8) :: ROWCN, COLCN, AMAX
     REAL(8), DIMENSION(:) :: R, C

  C INTERFACE
     #include <sunperf.h>

     void zgbequ(int m, int n, int kl, int ku, doublecomplex  *a,
               int lda, double *r, double *c, double *rowcn, dou-
               ble *colcn, double *amax, int *info);
     void zgbequ_64(long m, long n, long kl, long ku,  doublecom-
               plex  *a,  long  lda, double *r, double *c, double
               *rowcn, double *colcn, double *amax, long *info);

PURPOSE

     zgbequ computes row and column scalings intended to  equili-
     brate  an  M-by-N  band  matrix  A  and reduce its condition
     number.  R returns the row scale factors and  C  the  column
     scale  factors, chosen to try to make the largest element in
     each  row  and  column  of  the  matrix  B   with   elements
     B(i,j)=R(i)*A(i,j)*C(j) have absolute value 1.

     R(i) and C(j) are restricted to be between SMLNUM = smallest
     safe  number and BIGNUM = largest safe number.  Use of these
     scaling factors is not guaranteed to  reduce  the  condition
     number of A but works well in practice.

ARGUMENTS

     M (input) The number of rows of the matrix A.  M >= 0.

     N (input) The number of columns 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) The band matrix A, stored in rows  1  to  KL+KU+1.
               The  j-th column of A is stored in the j-th column
               of the array A as follows:  A(ku+1+i-j,j) = A(i,j)
               for max(1,j-ku)<=i<=min(m,j+kl).

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

     R (output)
               If INFO = 0, or INFO > M, R contains the row scale
               factors for A.
     C (output)
               If INFO = 0, C contains the column  scale  factors
               for A.

     ROWCN (output)
               If INFO = 0 or INFO > M, ROWCN contains the  ratio
               of  the  smallest  R(i)  to  the largest R(i).  If
               ROWCN >= 0.1 and AMAX is neither too large nor too
               small, it is not worth scaling by R.

     COLCN (output)
               If INFO = 0, COLCN contains the ratio of the smal-
               lest  C(i)  to the largest C(i).  If COLCN >= 0.1,
               it is not worth scaling by C.

     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, and i is
               <= M:  the i-th row of A is exactly zero
               >  M:  the (i-M)-th column of A is exactly zero