LAPACK 3.3.0

cpoequ.f

Go to the documentation of this file.
00001       SUBROUTINE CPOEQU( N, A, LDA, S, SCOND, AMAX, INFO )
00002 *
00003 *  -- LAPACK routine (version 3.2) --
00004 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00005 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00006 *     November 2006
00007 *
00008 *     .. Scalar Arguments ..
00009       INTEGER            INFO, LDA, N
00010       REAL               AMAX, SCOND
00011 *     ..
00012 *     .. Array Arguments ..
00013       REAL               S( * )
00014       COMPLEX            A( LDA, * )
00015 *     ..
00016 *
00017 *  Purpose
00018 *  =======
00019 *
00020 *  CPOEQU computes row and column scalings intended to equilibrate a
00021 *  Hermitian positive definite matrix A and reduce its condition number
00022 *  (with respect to the two-norm).  S contains the scale factors,
00023 *  S(i) = 1/sqrt(A(i,i)), chosen so that the scaled matrix B with
00024 *  elements B(i,j) = S(i)*A(i,j)*S(j) has ones on the diagonal.  This
00025 *  choice of S puts the condition number of B within a factor N of the
00026 *  smallest possible condition number over all possible diagonal
00027 *  scalings.
00028 *
00029 *  Arguments
00030 *  =========
00031 *
00032 *  N       (input) INTEGER
00033 *          The order of the matrix A.  N >= 0.
00034 *
00035 *  A       (input) COMPLEX array, dimension (LDA,N)
00036 *          The N-by-N Hermitian positive definite matrix whose scaling
00037 *          factors are to be computed.  Only the diagonal elements of A
00038 *          are referenced.
00039 *
00040 *  LDA     (input) INTEGER
00041 *          The leading dimension of the array A.  LDA >= max(1,N).
00042 *
00043 *  S       (output) REAL array, dimension (N)
00044 *          If INFO = 0, S contains the scale factors for A.
00045 *
00046 *  SCOND   (output) REAL
00047 *          If INFO = 0, S contains the ratio of the smallest S(i) to
00048 *          the largest S(i).  If SCOND >= 0.1 and AMAX is neither too
00049 *          large nor too small, it is not worth scaling by S.
00050 *
00051 *  AMAX    (output) REAL
00052 *          Absolute value of largest matrix element.  If AMAX is very
00053 *          close to overflow or very close to underflow, the matrix
00054 *          should be scaled.
00055 *
00056 *  INFO    (output) INTEGER
00057 *          = 0:  successful exit
00058 *          < 0:  if INFO = -i, the i-th argument had an illegal value
00059 *          > 0:  if INFO = i, the i-th diagonal element is nonpositive.
00060 *
00061 *  =====================================================================
00062 *
00063 *     .. Parameters ..
00064       REAL               ZERO, ONE
00065       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
00066 *     ..
00067 *     .. Local Scalars ..
00068       INTEGER            I
00069       REAL               SMIN
00070 *     ..
00071 *     .. External Subroutines ..
00072       EXTERNAL           XERBLA
00073 *     ..
00074 *     .. Intrinsic Functions ..
00075       INTRINSIC          MAX, MIN, REAL, SQRT
00076 *     ..
00077 *     .. Executable Statements ..
00078 *
00079 *     Test the input parameters.
00080 *
00081       INFO = 0
00082       IF( N.LT.0 ) THEN
00083          INFO = -1
00084       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
00085          INFO = -3
00086       END IF
00087       IF( INFO.NE.0 ) THEN
00088          CALL XERBLA( 'CPOEQU', -INFO )
00089          RETURN
00090       END IF
00091 *
00092 *     Quick return if possible
00093 *
00094       IF( N.EQ.0 ) THEN
00095          SCOND = ONE
00096          AMAX = ZERO
00097          RETURN
00098       END IF
00099 *
00100 *     Find the minimum and maximum diagonal elements.
00101 *
00102       S( 1 ) = REAL( A( 1, 1 ) )
00103       SMIN = S( 1 )
00104       AMAX = S( 1 )
00105       DO 10 I = 2, N
00106          S( I ) = REAL( A( I, I ) )
00107          SMIN = MIN( SMIN, S( I ) )
00108          AMAX = MAX( AMAX, S( I ) )
00109    10 CONTINUE
00110 *
00111       IF( SMIN.LE.ZERO ) THEN
00112 *
00113 *        Find the first non-positive diagonal element and return.
00114 *
00115          DO 20 I = 1, N
00116             IF( S( I ).LE.ZERO ) THEN
00117                INFO = I
00118                RETURN
00119             END IF
00120    20    CONTINUE
00121       ELSE
00122 *
00123 *        Set the scale factors to the reciprocals
00124 *        of the diagonal elements.
00125 *
00126          DO 30 I = 1, N
00127             S( I ) = ONE / SQRT( S( I ) )
00128    30    CONTINUE
00129 *
00130 *        Compute SCOND = min(S(I)) / max(S(I))
00131 *
00132          SCOND = SQRT( SMIN ) / SQRT( AMAX )
00133       END IF
00134       RETURN
00135 *
00136 *     End of CPOEQU
00137 *
00138       END
 All Files Functions