1       SUBROUTINE ZPOEQU( N, A, LDA, S, SCOND, AMAX, INFO )
  2 *
  3 *  -- LAPACK routine (version 3.2) --
  4 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  5 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  6 *     November 2006
  7 *
  8 *     .. Scalar Arguments ..
  9       INTEGER            INFO, LDA, N
 10       DOUBLE PRECISION   AMAX, SCOND
 11 *     ..
 12 *     .. Array Arguments ..
 13       DOUBLE PRECISION   S( * )
 14       COMPLEX*16         A( LDA, * )
 15 *     ..
 16 *
 17 *  Purpose
 18 *  =======
 19 *
 20 *  ZPOEQU computes row and column scalings intended to equilibrate a
 21 *  Hermitian positive definite matrix A and reduce its condition number
 22 *  (with respect to the two-norm).  S contains the scale factors,
 23 *  S(i) = 1/sqrt(A(i,i)), chosen so that the scaled matrix B with
 24 *  elements B(i,j) = S(i)*A(i,j)*S(j) has ones on the diagonal.  This
 25 *  choice of S puts the condition number of B within a factor N of the
 26 *  smallest possible condition number over all possible diagonal
 27 *  scalings.
 28 *
 29 *  Arguments
 30 *  =========
 31 *
 32 *  N       (input) INTEGER
 33 *          The order of the matrix A.  N >= 0.
 34 *
 35 *  A       (input) COMPLEX*16 array, dimension (LDA,N)
 36 *          The N-by-N Hermitian positive definite matrix whose scaling
 37 *          factors are to be computed.  Only the diagonal elements of A
 38 *          are referenced.
 39 *
 40 *  LDA     (input) INTEGER
 41 *          The leading dimension of the array A.  LDA >= max(1,N).
 42 *
 43 *  S       (output) DOUBLE PRECISION array, dimension (N)
 44 *          If INFO = 0, S contains the scale factors for A.
 45 *
 46 *  SCOND   (output) DOUBLE PRECISION
 47 *          If INFO = 0, S contains the ratio of the smallest S(i) to
 48 *          the largest S(i).  If SCOND >= 0.1 and AMAX is neither too
 49 *          large nor too small, it is not worth scaling by S.
 50 *
 51 *  AMAX    (output) DOUBLE PRECISION
 52 *          Absolute value of largest matrix element.  If AMAX is very
 53 *          close to overflow or very close to underflow, the matrix
 54 *          should be scaled.
 55 *
 56 *  INFO    (output) INTEGER
 57 *          = 0:  successful exit
 58 *          < 0:  if INFO = -i, the i-th argument had an illegal value
 59 *          > 0:  if INFO = i, the i-th diagonal element is nonpositive.
 60 *
 61 *  =====================================================================
 62 *
 63 *     .. Parameters ..
 64       DOUBLE PRECISION   ZERO, ONE
 65       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
 66 *     ..
 67 *     .. Local Scalars ..
 68       INTEGER            I
 69       DOUBLE PRECISION   SMIN
 70 *     ..
 71 *     .. External Subroutines ..
 72       EXTERNAL           XERBLA
 73 *     ..
 74 *     .. Intrinsic Functions ..
 75       INTRINSIC          DBLEMAXMINSQRT
 76 *     ..
 77 *     .. Executable Statements ..
 78 *
 79 *     Test the input parameters.
 80 *
 81       INFO = 0
 82       IF( N.LT.0 ) THEN
 83          INFO = -1
 84       ELSE IF( LDA.LT.MAX1, N ) ) THEN
 85          INFO = -3
 86       END IF
 87       IF( INFO.NE.0 ) THEN
 88          CALL XERBLA( 'ZPOEQU'-INFO )
 89          RETURN
 90       END IF
 91 *
 92 *     Quick return if possible
 93 *
 94       IF( N.EQ.0 ) THEN
 95          SCOND = ONE
 96          AMAX = ZERO
 97          RETURN
 98       END IF
 99 *
100 *     Find the minimum and maximum diagonal elements.
101 *
102       S( 1 ) = DBLE( A( 11 ) )
103       SMIN = S( 1 )
104       AMAX = S( 1 )
105       DO 10 I = 2, N
106          S( I ) = DBLE( A( I, I ) )
107          SMIN = MIN( SMIN, S( I ) )
108          AMAX = MAX( AMAX, S( I ) )
109    10 CONTINUE
110 *
111       IF( SMIN.LE.ZERO ) THEN
112 *
113 *        Find the first non-positive diagonal element and return.
114 *
115          DO 20 I = 1, N
116             IF( S( I ).LE.ZERO ) THEN
117                INFO = I
118                RETURN
119             END IF
120    20    CONTINUE
121       ELSE
122 *
123 *        Set the scale factors to the reciprocals
124 *        of the diagonal elements.
125 *
126          DO 30 I = 1, N
127             S( I ) = ONE / SQRT( S( I ) )
128    30    CONTINUE
129 *
130 *        Compute SCOND = min(S(I)) / max(S(I))
131 *
132          SCOND = SQRT( SMIN ) / SQRT( AMAX )
133       END IF
134       RETURN
135 *
136 *     End of ZPOEQU
137 *
138       END