Contents


NAME

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

SYNOPSIS

     SUBROUTINE ZPOEQU(N, A, LDA, SCALE, SCOND, AMAX, INFO)

     DOUBLE COMPLEX A(LDA,*)
     INTEGER N, LDA, INFO
     DOUBLE PRECISION SCOND, AMAX
     DOUBLE PRECISION SCALE(*)

     SUBROUTINE ZPOEQU_64(N, A, LDA, SCALE, SCOND, AMAX, INFO)

     DOUBLE COMPLEX A(LDA,*)
     INTEGER*8 N, LDA, INFO
     DOUBLE PRECISION SCOND, AMAX
     DOUBLE PRECISION SCALE(*)

  F95 INTERFACE
     SUBROUTINE POEQU([N], A, [LDA], SCALE, SCOND, AMAX, [INFO])

     COMPLEX(8), DIMENSION(:,:) :: A
     INTEGER :: N, LDA, INFO
     REAL(8) :: SCOND, AMAX
     REAL(8), DIMENSION(:) :: SCALE

     SUBROUTINE POEQU_64([N], A, [LDA], SCALE, SCOND, AMAX, [INFO])

     COMPLEX(8), DIMENSION(:,:) :: A
     INTEGER(8) :: N, LDA, INFO
     REAL(8) :: SCOND, AMAX
     REAL(8), DIMENSION(:) :: SCALE

  C INTERFACE
     #include <sunperf.h>

     void zpoequ(int n, doublecomplex *a, int lda, double *scale,
               double *scond, double *amax, int *info);

     void zpoequ_64(long n, doublecomplex *a,  long  lda,  double
               *scale, double *scond, double *amax, long *info);

PURPOSE

     zpoequ  computes  row  and  column  scalings   intended   to
     equilibrate  a  Hermitian  positive  definite  matrix  A and
     reduce its condition number (with respect to the  two-norm).
     S  contains 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

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

     A (input) The  N-by-N  Hermitian  positive  definite  matrix
               whose  scaling  factors  are to be computed.  Only
               the diagonal elements of A are referenced.

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

     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.