LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zheequb.f
Go to the documentation of this file.
1*> \brief \b ZHEEQUB
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZHEEQUB + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zheequb.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zheequb.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheequb.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZHEEQUB( UPLO, N, A, LDA, S, SCOND, AMAX, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, LDA, N
23* DOUBLE PRECISION AMAX, SCOND
24* CHARACTER UPLO
25* ..
26* .. Array Arguments ..
27* COMPLEX*16 A( LDA, * ), WORK( * )
28* DOUBLE PRECISION S( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZHEEQUB computes row and column scalings intended to equilibrate a
38*> Hermitian matrix A (with respect to the Euclidean norm) and reduce
39*> its condition number. The scale factors S are computed by the BIN
40*> algorithm (see references) so that the scaled matrix B with elements
41*> B(i,j) = S(i)*A(i,j)*S(j) has a condition number within a factor N of
42*> the smallest possible condition number over all possible diagonal
43*> scalings.
44*> \endverbatim
45*
46* Arguments:
47* ==========
48*
49*> \param[in] UPLO
50*> \verbatim
51*> UPLO is CHARACTER*1
52*> = 'U': Upper triangle of A is stored;
53*> = 'L': Lower triangle of A is stored.
54*> \endverbatim
55*>
56*> \param[in] N
57*> \verbatim
58*> N is INTEGER
59*> The order of the matrix A. N >= 0.
60*> \endverbatim
61*>
62*> \param[in] A
63*> \verbatim
64*> A is COMPLEX*16 array, dimension (LDA,N)
65*> The N-by-N Hermitian matrix whose scaling factors are to be
66*> computed.
67*> \endverbatim
68*>
69*> \param[in] LDA
70*> \verbatim
71*> LDA is INTEGER
72*> The leading dimension of the array A. LDA >= max(1,N).
73*> \endverbatim
74*>
75*> \param[out] S
76*> \verbatim
77*> S is DOUBLE PRECISION array, dimension (N)
78*> If INFO = 0, S contains the scale factors for A.
79*> \endverbatim
80*>
81*> \param[out] SCOND
82*> \verbatim
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.
87*> \endverbatim
88*>
89*> \param[out] AMAX
90*> \verbatim
91*> AMAX is DOUBLE PRECISION
92*> Largest absolute value of any matrix element. If AMAX is
93*> very close to overflow or very close to underflow, the
94*> matrix should be scaled.
95*> \endverbatim
96*>
97*> \param[out] WORK
98*> \verbatim
99*> WORK is COMPLEX*16 array, dimension (2*N)
100*> \endverbatim
101*>
102*> \param[out] INFO
103*> \verbatim
104*> INFO is INTEGER
105*> = 0: successful exit
106*> < 0: if INFO = -i, the i-th argument had an illegal value
107*> > 0: if INFO = i, the i-th diagonal element is nonpositive.
108*> \endverbatim
109*
110* Authors:
111* ========
112*
113*> \author Univ. of Tennessee
114*> \author Univ. of California Berkeley
115*> \author Univ. of Colorado Denver
116*> \author NAG Ltd.
117*
118*> \ingroup heequb
119*
120*> \par References:
121* ================
122*>
123*> Livne, O.E. and Golub, G.H., "Scaling by Binormalization", \n
124*> Numerical Algorithms, vol. 35, no. 1, pp. 97-120, January 2004. \n
125*> DOI 10.1023/B:NUMA.0000016606.32820.69 \n
126*> Tech report version: http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.3.1679
127*>
128* =====================================================================
129 SUBROUTINE zheequb( UPLO, N, A, LDA, S, SCOND, AMAX, WORK,
130 $ INFO )
131*
132* -- LAPACK computational routine --
133* -- LAPACK is a software package provided by Univ. of Tennessee, --
134* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
135*
136* .. Scalar Arguments ..
137 INTEGER INFO, LDA, N
138 DOUBLE PRECISION AMAX, SCOND
139 CHARACTER UPLO
140* ..
141* .. Array Arguments ..
142 COMPLEX*16 A( LDA, * ), WORK( * )
143 DOUBLE PRECISION S( * )
144* ..
145*
146* =====================================================================
147*
148* .. Parameters ..
149 DOUBLE PRECISION ONE, ZERO
150 parameter( one = 1.0d0, zero = 0.0d0 )
151 INTEGER MAX_ITER
152 parameter( max_iter = 100 )
153* ..
154* .. Local Scalars ..
155 INTEGER I, J, ITER
156 DOUBLE PRECISION AVG, STD, TOL, C0, C1, C2, T, U, SI, D, BASE,
157 $ smin, smax, smlnum, bignum, scale, sumsq
158 LOGICAL UP
159 COMPLEX*16 ZDUM
160* ..
161* .. External Functions ..
162 DOUBLE PRECISION DLAMCH
163 LOGICAL LSAME
164 EXTERNAL dlamch, lsame
165* ..
166* .. External Subroutines ..
167 EXTERNAL zlassq, xerbla
168* ..
169* .. Intrinsic Functions ..
170 INTRINSIC abs, dble, dimag, int, log, max, min, sqrt
171* ..
172* .. Statement Functions ..
173 DOUBLE PRECISION CABS1
174* ..
175* .. Statement Function Definitions ..
176 cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
177* ..
178* .. Executable Statements ..
179*
180* Test the input parameters.
181*
182 info = 0
183 IF ( .NOT. ( lsame( uplo, 'U' ) .OR.
184 $ lsame( uplo, 'L' ) ) ) THEN
185 info = -1
186 ELSE IF ( n .LT. 0 ) THEN
187 info = -2
188 ELSE IF ( lda .LT. max( 1, n ) ) THEN
189 info = -4
190 END IF
191 IF ( info .NE. 0 ) THEN
192 CALL xerbla( 'ZHEEQUB', -info )
193 RETURN
194 END IF
195
196 up = lsame( uplo, 'U' )
197 amax = zero
198*
199* Quick return if possible.
200*
201 IF ( n .EQ. 0 ) THEN
202 scond = one
203 RETURN
204 END IF
205
206 DO i = 1, n
207 s( i ) = zero
208 END DO
209
210 amax = zero
211 IF ( up ) THEN
212 DO j = 1, n
213 DO i = 1, j-1
214 s( i ) = max( s( i ), cabs1( a( i, j ) ) )
215 s( j ) = max( s( j ), cabs1( a( i, j ) ) )
216 amax = max( amax, cabs1( a( i, j ) ) )
217 END DO
218 s( j ) = max( s( j ), cabs1( a( j, j ) ) )
219 amax = max( amax, cabs1( a( j, j ) ) )
220 END DO
221 ELSE
222 DO j = 1, n
223 s( j ) = max( s( j ), cabs1( a( j, j ) ) )
224 amax = max( amax, cabs1( a( j, j ) ) )
225 DO i = j+1, n
226 s( i ) = max( s( i ), cabs1( a( i, j ) ) )
227 s( j ) = max( s( j ), cabs1( a( i, j ) ) )
228 amax = max( amax, cabs1( a( i, j ) ) )
229 END DO
230 END DO
231 END IF
232 DO j = 1, n
233 s( j ) = 1.0d0 / s( j )
234 END DO
235
236 tol = one / sqrt( 2.0d0 * n )
237
238 DO iter = 1, max_iter
239 scale = 0.0d0
240 sumsq = 0.0d0
241* beta = |A|s
242 DO i = 1, n
243 work( i ) = zero
244 END DO
245 IF ( up ) THEN
246 DO j = 1, n
247 DO i = 1, j-1
248 work( i ) = work( i ) + cabs1( a( i, j ) ) * s( j )
249 work( j ) = work( j ) + cabs1( a( i, j ) ) * s( i )
250 END DO
251 work( j ) = work( j ) + cabs1( a( j, j ) ) * s( j )
252 END DO
253 ELSE
254 DO j = 1, n
255 work( j ) = work( j ) + cabs1( a( j, j ) ) * s( j )
256 DO i = j+1, n
257 work( i ) = work( i ) + cabs1( a( i, j ) ) * s( j )
258 work( j ) = work( j ) + cabs1( a( i, j ) ) * s( i )
259 END DO
260 END DO
261 END IF
262
263* avg = s^T beta / n
264 avg = 0.0d0
265 DO i = 1, n
266 avg = avg + dble( s( i )*work( i ) )
267 END DO
268 avg = avg / n
269
270 std = 0.0d0
271 DO i = n+1, 2*n
272 work( i ) = s( i-n ) * work( i-n ) - avg
273 END DO
274 CALL zlassq( n, work( n+1 ), 1, scale, sumsq )
275 std = scale * sqrt( sumsq / n )
276
277 IF ( std .LT. tol * avg ) GOTO 999
278
279 DO i = 1, n
280 t = cabs1( a( i, i ) )
281 si = s( i )
282 c2 = ( n-1 ) * t
283 c1 = ( n-2 ) * ( dble( work( i ) ) - t*si )
284 c0 = -(t*si)*si + 2 * dble( work( i ) ) * si - n*avg
285 d = c1*c1 - 4*c0*c2
286
287 IF ( d .LE. 0 ) THEN
288 info = -1
289 RETURN
290 END IF
291 si = -2*c0 / ( c1 + sqrt( d ) )
292
293 d = si - s( i )
294 u = zero
295 IF ( up ) THEN
296 DO j = 1, i
297 t = cabs1( a( j, i ) )
298 u = u + s( j )*t
299 work( j ) = work( j ) + d*t
300 END DO
301 DO j = i+1,n
302 t = cabs1( a( i, j ) )
303 u = u + s( j )*t
304 work( j ) = work( j ) + d*t
305 END DO
306 ELSE
307 DO j = 1, i
308 t = cabs1( a( i, j ) )
309 u = u + s( j )*t
310 work( j ) = work( j ) + d*t
311 END DO
312 DO j = i+1,n
313 t = cabs1( a( j, i ) )
314 u = u + s( j )*t
315 work( j ) = work( j ) + d*t
316 END DO
317 END IF
318
319 avg = avg + ( u + dble( work( i ) ) ) * d / n
320 s( i ) = si
321 END DO
322 END DO
323
324 999 CONTINUE
325
326 smlnum = dlamch( 'SAFEMIN' )
327 bignum = one / smlnum
328 smin = bignum
329 smax = zero
330 t = one / sqrt( avg )
331 base = dlamch( 'B' )
332 u = one / log( base )
333 DO i = 1, n
334 s( i ) = base ** int( u * log( s( i ) * t ) )
335 smin = min( smin, s( i ) )
336 smax = max( smax, s( i ) )
337 END DO
338 scond = max( smin, smlnum ) / min( smax, bignum )
339*
340 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zheequb(uplo, n, a, lda, s, scond, amax, work, info)
ZHEEQUB
Definition zheequb.f:131
subroutine zlassq(n, x, incx, scale, sumsq)
ZLASSQ updates a sum of squares represented in scaled form.
Definition zlassq.f90:122