3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZPPEQU + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zppequ.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zppequ.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zppequ.f">
21 * SUBROUTINE ZPPEQU( UPLO, N, AP, S, SCOND, AMAX, INFO )
23 * .. Scalar Arguments ..
26 * DOUBLE PRECISION AMAX, SCOND
28 * .. Array Arguments ..
29 * DOUBLE PRECISION S( * )
39 *> ZPPEQU computes row and column scalings intended to equilibrate a
40 *> Hermitian positive definite matrix A in packed storage and reduce
41 *> its condition number (with respect to the two-norm). S contains the
42 *> scale factors, S(i)=1/sqrt(A(i,i)), chosen so that the scaled matrix
43 *> B with elements B(i,j)=S(i)*A(i,j)*S(j) has ones on the diagonal.
44 *> This choice of S puts the condition number of B within a factor N of
45 *> the smallest possible condition number over all possible diagonal
54 *> UPLO is CHARACTER*1
55 *> = 'U': Upper triangle of A is stored;
56 *> = 'L': Lower triangle of A is stored.
62 *> The order of the matrix A. N >= 0.
67 *> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
68 *> The upper or lower triangle of the Hermitian matrix A, packed
69 *> columnwise in a linear array. The j-th column of A is stored
70 *> in the array AP as follows:
71 *> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
72 *> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
77 *> S is DOUBLE PRECISION array, dimension (N)
78 *> If INFO = 0, S contains the scale factors for A.
83 *> SCOND is DOUBLE PRECISION
84 *> If INFO = 0, S contains the ratio of the smallest S(i) to
85 *> the largest S(i). If SCOND >= 0.1 and AMAX is neither too
86 *> large nor too small, it is not worth scaling by S.
91 *> AMAX is DOUBLE PRECISION
92 *> Absolute value of largest matrix element. If AMAX is very
93 *> close to overflow or very close to underflow, the matrix
100 *> = 0: successful exit
101 *> < 0: if INFO = -i, the i-th argument had an illegal value
102 *> > 0: if INFO = i, the i-th diagonal element is nonpositive.
108 *> \author Univ. of Tennessee
109 *> \author Univ. of California Berkeley
110 *> \author Univ. of Colorado Denver
113 *> \date November 2011
115 *> \ingroup complex16OTHERcomputational
117 * =====================================================================
118 SUBROUTINE ZPPEQU( UPLO, N, AP, S, SCOND, AMAX, INFO )
120 * -- LAPACK computational routine (version 3.4.0) --
121 * -- LAPACK is a software package provided by Univ. of Tennessee, --
122 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
125 * .. Scalar Arguments ..
128 DOUBLE PRECISION AMAX, SCOND
130 * .. Array Arguments ..
131 DOUBLE PRECISION S( * )
135 * =====================================================================
138 DOUBLE PRECISION ONE, ZERO
139 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
141 * .. Local Scalars ..
144 DOUBLE PRECISION SMIN
146 * .. External Functions ..
150 * .. External Subroutines ..
153 * .. Intrinsic Functions ..
154 INTRINSIC DBLE, MAX, MIN, SQRT
156 * .. Executable Statements ..
158 * Test the input parameters.
161 UPPER = LSAME( UPLO, 'U' )
162 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
164 ELSE IF( N.LT.0 ) THEN
168 CALL XERBLA( 'ZPPEQU', -INFO )
172 * Quick return if possible
180 * Initialize SMIN and AMAX.
182 S( 1 ) = DBLE( AP( 1 ) )
188 * UPLO = 'U': Upper triangle of A is stored.
189 * Find the minimum and maximum diagonal elements.
194 S( I ) = DBLE( AP( JJ ) )
195 SMIN = MIN( SMIN, S( I ) )
196 AMAX = MAX( AMAX, S( I ) )
201 * UPLO = 'L': Lower triangle of A is stored.
202 * Find the minimum and maximum diagonal elements.
207 S( I ) = DBLE( AP( JJ ) )
208 SMIN = MIN( SMIN, S( I ) )
209 AMAX = MAX( AMAX, S( I ) )
213 IF( SMIN.LE.ZERO ) THEN
215 * Find the first non-positive diagonal element and return.
218 IF( S( I ).LE.ZERO ) THEN
225 * Set the scale factors to the reciprocals
226 * of the diagonal elements.
229 S( I ) = ONE / SQRT( S( I ) )
232 * Compute SCOND = min(S(I)) / max(S(I))
234 SCOND = SQRT( SMIN ) / SQRT( AMAX )