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