LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cgebal.f
Go to the documentation of this file.
1 *> \brief \b CGEBAL
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CGEBAL + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgebal.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgebal.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgebal.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CGEBAL( JOB, N, A, LDA, ILO, IHI, SCALE, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER JOB
25 * INTEGER IHI, ILO, INFO, LDA, N
26 * ..
27 * .. Array Arguments ..
28 * REAL SCALE( * )
29 * COMPLEX A( LDA, * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> CGEBAL balances a general complex matrix A. This involves, first,
39 *> permuting A by a similarity transformation to isolate eigenvalues
40 *> in the first 1 to ILO-1 and last IHI+1 to N elements on the
41 *> diagonal; and second, applying a diagonal similarity transformation
42 *> to rows and columns ILO to IHI to make the rows and columns as
43 *> close in norm as possible. Both steps are optional.
44 *>
45 *> Balancing may reduce the 1-norm of the matrix, and improve the
46 *> accuracy of the computed eigenvalues and/or eigenvectors.
47 *> \endverbatim
48 *
49 * Arguments:
50 * ==========
51 *
52 *> \param[in] JOB
53 *> \verbatim
54 *> JOB is CHARACTER*1
55 *> Specifies the operations to be performed on A:
56 *> = 'N': none: simply set ILO = 1, IHI = N, SCALE(I) = 1.0
57 *> for i = 1,...,N;
58 *> = 'P': permute only;
59 *> = 'S': scale only;
60 *> = 'B': both permute and scale.
61 *> \endverbatim
62 *>
63 *> \param[in] N
64 *> \verbatim
65 *> N is INTEGER
66 *> The order of the matrix A. N >= 0.
67 *> \endverbatim
68 *>
69 *> \param[in,out] A
70 *> \verbatim
71 *> A is COMPLEX array, dimension (LDA,N)
72 *> On entry, the input matrix A.
73 *> On exit, A is overwritten by the balanced matrix.
74 *> If JOB = 'N', A is not referenced.
75 *> See Further Details.
76 *> \endverbatim
77 *>
78 *> \param[in] LDA
79 *> \verbatim
80 *> LDA is INTEGER
81 *> The leading dimension of the array A. LDA >= max(1,N).
82 *> \endverbatim
83 *>
84 *> \param[out] ILO
85 *> \verbatim
86 *> ILO is INTEGER
87 *> \endverbatim
88 *> \param[out] IHI
89 *> \verbatim
90 *> IHI is INTEGER
91 *> ILO and IHI are set to integers such that on exit
92 *> A(i,j) = 0 if i > j and j = 1,...,ILO-1 or I = IHI+1,...,N.
93 *> If JOB = 'N' or 'S', ILO = 1 and IHI = N.
94 *> \endverbatim
95 *>
96 *> \param[out] SCALE
97 *> \verbatim
98 *> SCALE is REAL array, dimension (N)
99 *> Details of the permutations and scaling factors applied to
100 *> A. If P(j) is the index of the row and column interchanged
101 *> with row and column j and D(j) is the scaling factor
102 *> applied to row and column j, then
103 *> SCALE(j) = P(j) for j = 1,...,ILO-1
104 *> = D(j) for j = ILO,...,IHI
105 *> = P(j) for j = IHI+1,...,N.
106 *> The order in which the interchanges are made is N to IHI+1,
107 *> then 1 to ILO-1.
108 *> \endverbatim
109 *>
110 *> \param[out] INFO
111 *> \verbatim
112 *> INFO is INTEGER
113 *> = 0: successful exit.
114 *> < 0: if INFO = -i, the i-th argument had an illegal value.
115 *> \endverbatim
116 *
117 * Authors:
118 * ========
119 *
120 *> \author Univ. of Tennessee
121 *> \author Univ. of California Berkeley
122 *> \author Univ. of Colorado Denver
123 *> \author NAG Ltd.
124 *
125 *> \date November 2011
126 *
127 *> \ingroup complexGEcomputational
128 *
129 *> \par Further Details:
130 * =====================
131 *>
132 *> \verbatim
133 *>
134 *> The permutations consist of row and column interchanges which put
135 *> the matrix in the form
136 *>
137 *> ( T1 X Y )
138 *> P A P = ( 0 B Z )
139 *> ( 0 0 T2 )
140 *>
141 *> where T1 and T2 are upper triangular matrices whose eigenvalues lie
142 *> along the diagonal. The column indices ILO and IHI mark the starting
143 *> and ending columns of the submatrix B. Balancing consists of applying
144 *> a diagonal similarity transformation inv(D) * B * D to make the
145 *> 1-norms of each row of B and its corresponding column nearly equal.
146 *> The output matrix is
147 *>
148 *> ( T1 X*D Y )
149 *> ( 0 inv(D)*B*D inv(D)*Z ).
150 *> ( 0 0 T2 )
151 *>
152 *> Information about the permutations P and the diagonal matrix D is
153 *> returned in the vector SCALE.
154 *>
155 *> This subroutine is based on the EISPACK routine CBAL.
156 *>
157 *> Modified by Tzu-Yi Chen, Computer Science Division, University of
158 *> California at Berkeley, USA
159 *> \endverbatim
160 *>
161 * =====================================================================
162  SUBROUTINE cgebal( JOB, N, A, LDA, ILO, IHI, SCALE, INFO )
163 *
164 * -- LAPACK computational routine (version 3.4.0) --
165 * -- LAPACK is a software package provided by Univ. of Tennessee, --
166 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
167 * November 2011
168 *
169 * .. Scalar Arguments ..
170  CHARACTER job
171  INTEGER ihi, ilo, info, lda, n
172 * ..
173 * .. Array Arguments ..
174  REAL scale( * )
175  COMPLEX a( lda, * )
176 * ..
177 *
178 * =====================================================================
179 *
180 * .. Parameters ..
181  REAL zero, one
182  parameter( zero = 0.0e+0, one = 1.0e+0 )
183  REAL sclfac
184  parameter( sclfac = 2.0e+0 )
185  REAL factor
186  parameter( factor = 0.95e+0 )
187 * ..
188 * .. Local Scalars ..
189  LOGICAL noconv
190  INTEGER i, ica, iexc, ira, j, k, l, m
191  REAL c, ca, f, g, r, ra, s, sfmax1, sfmax2, sfmin1,
192  $ sfmin2
193  COMPLEX cdum
194 * ..
195 * .. External Functions ..
196  LOGICAL sisnan, lsame
197  INTEGER icamax
198  REAL slamch
199  EXTERNAL sisnan, lsame, icamax, slamch
200 * ..
201 * .. External Subroutines ..
202  EXTERNAL csscal, cswap, xerbla
203 * ..
204 * .. Intrinsic Functions ..
205  INTRINSIC abs, aimag, max, min, real
206 * ..
207 * .. Statement Functions ..
208  REAL cabs1
209 * ..
210 * .. Statement Function definitions ..
211  cabs1( cdum ) = abs( REAL( CDUM ) ) + abs( aimag( cdum ) )
212 * ..
213 * .. Executable Statements ..
214 *
215 * Test the input parameters
216 *
217  info = 0
218  IF( .NOT.lsame( job, 'N' ) .AND. .NOT.lsame( job, 'P' ) .AND.
219  $ .NOT.lsame( job, 'S' ) .AND. .NOT.lsame( job, 'B' ) ) THEN
220  info = -1
221  ELSE IF( n.LT.0 ) THEN
222  info = -2
223  ELSE IF( lda.LT.max( 1, n ) ) THEN
224  info = -4
225  END IF
226  IF( info.NE.0 ) THEN
227  CALL xerbla( 'CGEBAL', -info )
228  return
229  END IF
230 *
231  k = 1
232  l = n
233 *
234  IF( n.EQ.0 )
235  $ go to 210
236 *
237  IF( lsame( job, 'N' ) ) THEN
238  DO 10 i = 1, n
239  scale( i ) = one
240  10 continue
241  go to 210
242  END IF
243 *
244  IF( lsame( job, 'S' ) )
245  $ go to 120
246 *
247 * Permutation to isolate eigenvalues if possible
248 *
249  go to 50
250 *
251 * Row and column exchange.
252 *
253  20 continue
254  scale( m ) = j
255  IF( j.EQ.m )
256  $ go to 30
257 *
258  CALL cswap( l, a( 1, j ), 1, a( 1, m ), 1 )
259  CALL cswap( n-k+1, a( j, k ), lda, a( m, k ), lda )
260 *
261  30 continue
262  go to( 40, 80 )iexc
263 *
264 * Search for rows isolating an eigenvalue and push them down.
265 *
266  40 continue
267  IF( l.EQ.1 )
268  $ go to 210
269  l = l - 1
270 *
271  50 continue
272  DO 70 j = l, 1, -1
273 *
274  DO 60 i = 1, l
275  IF( i.EQ.j )
276  $ go to 60
277  IF( REAL( A( J, I ) ).NE.zero .OR. aimag( a( j, i ) ).NE.
278  $ zero )go to 70
279  60 continue
280 *
281  m = l
282  iexc = 1
283  go to 20
284  70 continue
285 *
286  go to 90
287 *
288 * Search for columns isolating an eigenvalue and push them left.
289 *
290  80 continue
291  k = k + 1
292 *
293  90 continue
294  DO 110 j = k, l
295 *
296  DO 100 i = k, l
297  IF( i.EQ.j )
298  $ go to 100
299  IF( REAL( A( I, J ) ).NE.zero .OR. aimag( a( i, j ) ).NE.
300  $ zero )go to 110
301  100 continue
302 *
303  m = k
304  iexc = 2
305  go to 20
306  110 continue
307 *
308  120 continue
309  DO 130 i = k, l
310  scale( i ) = one
311  130 continue
312 *
313  IF( lsame( job, 'P' ) )
314  $ go to 210
315 *
316 * Balance the submatrix in rows K to L.
317 *
318 * Iterative loop for norm reduction
319 *
320  sfmin1 = slamch( 'S' ) / slamch( 'P' )
321  sfmax1 = one / sfmin1
322  sfmin2 = sfmin1*sclfac
323  sfmax2 = one / sfmin2
324  140 continue
325  noconv = .false.
326 *
327  DO 200 i = k, l
328  c = zero
329  r = zero
330 *
331  DO 150 j = k, l
332  IF( j.EQ.i )
333  $ go to 150
334  c = c + cabs1( a( j, i ) )
335  r = r + cabs1( a( i, j ) )
336  150 continue
337  ica = icamax( l, a( 1, i ), 1 )
338  ca = abs( a( ica, i ) )
339  ira = icamax( n-k+1, a( i, k ), lda )
340  ra = abs( a( i, ira+k-1 ) )
341 *
342 * Guard against zero C or R due to underflow.
343 *
344  IF( c.EQ.zero .OR. r.EQ.zero )
345  $ go to 200
346  g = r / sclfac
347  f = one
348  s = c + r
349  160 continue
350  IF( c.GE.g .OR. max( f, c, ca ).GE.sfmax2 .OR.
351  $ min( r, g, ra ).LE.sfmin2 )go to 170
352  IF( sisnan( c+f+ca+r+g+ra ) ) THEN
353 *
354 * Exit if NaN to avoid infinite loop
355 *
356  info = -3
357  CALL xerbla( 'CGEBAL', -info )
358  return
359  END IF
360  f = f*sclfac
361  c = c*sclfac
362  ca = ca*sclfac
363  r = r / sclfac
364  g = g / sclfac
365  ra = ra / sclfac
366  go to 160
367 *
368  170 continue
369  g = c / sclfac
370  180 continue
371  IF( g.LT.r .OR. max( r, ra ).GE.sfmax2 .OR.
372  $ min( f, c, g, ca ).LE.sfmin2 )go to 190
373  f = f / sclfac
374  c = c / sclfac
375  g = g / sclfac
376  ca = ca / sclfac
377  r = r*sclfac
378  ra = ra*sclfac
379  go to 180
380 *
381 * Now balance.
382 *
383  190 continue
384  IF( ( c+r ).GE.factor*s )
385  $ go to 200
386  IF( f.LT.one .AND. scale( i ).LT.one ) THEN
387  IF( f*scale( i ).LE.sfmin1 )
388  $ go to 200
389  END IF
390  IF( f.GT.one .AND. scale( i ).GT.one ) THEN
391  IF( scale( i ).GE.sfmax1 / f )
392  $ go to 200
393  END IF
394  g = one / f
395  scale( i ) = scale( i )*f
396  noconv = .true.
397 *
398  CALL csscal( n-k+1, g, a( i, k ), lda )
399  CALL csscal( l, f, a( 1, i ), 1 )
400 *
401  200 continue
402 *
403  IF( noconv )
404  $ go to 140
405 *
406  210 continue
407  ilo = k
408  ihi = l
409 *
410  return
411 *
412 * End of CGEBAL
413 *
414  END