LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
subroutine zgebal ( character  JOB,
integer  N,
complex*16, dimension( lda, * )  A,
integer  LDA,
integer  ILO,
integer  IHI,
double precision, dimension( * )  SCALE,
integer  INFO 
)

ZGEBAL

Download ZGEBAL + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZGEBAL balances a general complex matrix A.  This involves, first,
 permuting A by a similarity transformation to isolate eigenvalues
 in the first 1 to ILO-1 and last IHI+1 to N elements on the
 diagonal; and second, applying a diagonal similarity transformation
 to rows and columns ILO to IHI to make the rows and columns as
 close in norm as possible.  Both steps are optional.

 Balancing may reduce the 1-norm of the matrix, and improve the
 accuracy of the computed eigenvalues and/or eigenvectors.
Parameters
[in]JOB
          JOB is CHARACTER*1
          Specifies the operations to be performed on A:
          = 'N':  none:  simply set ILO = 1, IHI = N, SCALE(I) = 1.0
                  for i = 1,...,N;
          = 'P':  permute only;
          = 'S':  scale only;
          = 'B':  both permute and scale.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in,out]A
          A is COMPLEX*16 array, dimension (LDA,N)
          On entry, the input matrix A.
          On exit,  A is overwritten by the balanced matrix.
          If JOB = 'N', A is not referenced.
          See Further Details.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[out]ILO
 
[out]IHI
          ILO and IHI are set to INTEGER such that on exit
          A(i,j) = 0 if i > j and j = 1,...,ILO-1 or I = IHI+1,...,N.
          If JOB = 'N' or 'S', ILO = 1 and IHI = N.
[out]SCALE
          SCALE is DOUBLE PRECISION array, dimension (N)
          Details of the permutations and scaling factors applied to
          A.  If P(j) is the index of the row and column interchanged
          with row and column j and D(j) is the scaling factor
          applied to row and column j, then
          SCALE(j) = P(j)    for j = 1,...,ILO-1
                   = D(j)    for j = ILO,...,IHI
                   = P(j)    for j = IHI+1,...,N.
          The order in which the interchanges are made is N to IHI+1,
          then 1 to ILO-1.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit.
          < 0:  if INFO = -i, the i-th argument had an illegal value.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
December 2016
Further Details:
  The permutations consist of row and column interchanges which put
  the matrix in the form

             ( T1   X   Y  )
     P A P = (  0   B   Z  )
             (  0   0   T2 )

  where T1 and T2 are upper triangular matrices whose eigenvalues lie
  along the diagonal.  The column indices ILO and IHI mark the starting
  and ending columns of the submatrix B. Balancing consists of applying
  a diagonal similarity transformation inv(D) * B * D to make the
  1-norms of each row of B and its corresponding column nearly equal.
  The output matrix is

     ( T1     X*D          Y    )
     (  0  inv(D)*B*D  inv(D)*Z ).
     (  0      0           T2   )

  Information about the permutations P and the diagonal matrix D is
  returned in the vector SCALE.

  This subroutine is based on the EISPACK routine CBAL.

  Modified by Tzu-Yi Chen, Computer Science Division, University of
    California at Berkeley, USA

Definition at line 162 of file zgebal.f.

162 *
163 * -- LAPACK computational routine (version 3.7.0) --
164 * -- LAPACK is a software package provided by Univ. of Tennessee, --
165 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
166 * December 2016
167 *
168 * .. Scalar Arguments ..
169  CHARACTER job
170  INTEGER ihi, ilo, info, lda, n
171 * ..
172 * .. Array Arguments ..
173  DOUBLE PRECISION scale( * )
174  COMPLEX*16 a( lda, * )
175 * ..
176 *
177 * =====================================================================
178 *
179 * .. Parameters ..
180  DOUBLE PRECISION zero, one
181  parameter ( zero = 0.0d+0, one = 1.0d+0 )
182  DOUBLE PRECISION sclfac
183  parameter ( sclfac = 2.0d+0 )
184  DOUBLE PRECISION factor
185  parameter ( factor = 0.95d+0 )
186 * ..
187 * .. Local Scalars ..
188  LOGICAL noconv
189  INTEGER i, ica, iexc, ira, j, k, l, m
190  DOUBLE PRECISION c, ca, f, g, r, ra, s, sfmax1, sfmax2, sfmin1,
191  $ sfmin2
192 * ..
193 * .. External Functions ..
194  LOGICAL disnan, lsame
195  INTEGER izamax
196  DOUBLE PRECISION dlamch, dznrm2
197  EXTERNAL disnan, lsame, izamax, dlamch, dznrm2
198 * ..
199 * .. External Subroutines ..
200  EXTERNAL xerbla, zdscal, zswap
201 * ..
202 * .. Intrinsic Functions ..
203  INTRINSIC abs, dble, dimag, max, min
204 *
205 * Test the input parameters
206 *
207  info = 0
208  IF( .NOT.lsame( job, 'N' ) .AND. .NOT.lsame( job, 'P' ) .AND.
209  $ .NOT.lsame( job, 'S' ) .AND. .NOT.lsame( job, 'B' ) ) THEN
210  info = -1
211  ELSE IF( n.LT.0 ) THEN
212  info = -2
213  ELSE IF( lda.LT.max( 1, n ) ) THEN
214  info = -4
215  END IF
216  IF( info.NE.0 ) THEN
217  CALL xerbla( 'ZGEBAL', -info )
218  RETURN
219  END IF
220 *
221  k = 1
222  l = n
223 *
224  IF( n.EQ.0 )
225  $ GO TO 210
226 *
227  IF( lsame( job, 'N' ) ) THEN
228  DO 10 i = 1, n
229  scale( i ) = one
230  10 CONTINUE
231  GO TO 210
232  END IF
233 *
234  IF( lsame( job, 'S' ) )
235  $ GO TO 120
236 *
237 * Permutation to isolate eigenvalues if possible
238 *
239  GO TO 50
240 *
241 * Row and column exchange.
242 *
243  20 CONTINUE
244  scale( m ) = j
245  IF( j.EQ.m )
246  $ GO TO 30
247 *
248  CALL zswap( l, a( 1, j ), 1, a( 1, m ), 1 )
249  CALL zswap( n-k+1, a( j, k ), lda, a( m, k ), lda )
250 *
251  30 CONTINUE
252  GO TO ( 40, 80 )iexc
253 *
254 * Search for rows isolating an eigenvalue and push them down.
255 *
256  40 CONTINUE
257  IF( l.EQ.1 )
258  $ GO TO 210
259  l = l - 1
260 *
261  50 CONTINUE
262  DO 70 j = l, 1, -1
263 *
264  DO 60 i = 1, l
265  IF( i.EQ.j )
266  $ GO TO 60
267  IF( dble( a( j, i ) ).NE.zero .OR. dimag( a( j, i ) ).NE.
268  $ zero )GO TO 70
269  60 CONTINUE
270 *
271  m = l
272  iexc = 1
273  GO TO 20
274  70 CONTINUE
275 *
276  GO TO 90
277 *
278 * Search for columns isolating an eigenvalue and push them left.
279 *
280  80 CONTINUE
281  k = k + 1
282 *
283  90 CONTINUE
284  DO 110 j = k, l
285 *
286  DO 100 i = k, l
287  IF( i.EQ.j )
288  $ GO TO 100
289  IF( dble( a( i, j ) ).NE.zero .OR. dimag( a( i, j ) ).NE.
290  $ zero )GO TO 110
291  100 CONTINUE
292 *
293  m = k
294  iexc = 2
295  GO TO 20
296  110 CONTINUE
297 *
298  120 CONTINUE
299  DO 130 i = k, l
300  scale( i ) = one
301  130 CONTINUE
302 *
303  IF( lsame( job, 'P' ) )
304  $ GO TO 210
305 *
306 * Balance the submatrix in rows K to L.
307 *
308 * Iterative loop for norm reduction
309 *
310  sfmin1 = dlamch( 'S' ) / dlamch( 'P' )
311  sfmax1 = one / sfmin1
312  sfmin2 = sfmin1*sclfac
313  sfmax2 = one / sfmin2
314  140 CONTINUE
315  noconv = .false.
316 *
317  DO 200 i = k, l
318 *
319  c = dznrm2( l-k+1, a( k, i ), 1 )
320  r = dznrm2( l-k+1, a( i, k ), lda )
321  ica = izamax( l, a( 1, i ), 1 )
322  ca = abs( a( ica, i ) )
323  ira = izamax( n-k+1, a( i, k ), lda )
324  ra = abs( a( i, ira+k-1 ) )
325 *
326 * Guard against zero C or R due to underflow.
327 *
328  IF( c.EQ.zero .OR. r.EQ.zero )
329  $ GO TO 200
330  g = r / sclfac
331  f = one
332  s = c + r
333  160 CONTINUE
334  IF( c.GE.g .OR. max( f, c, ca ).GE.sfmax2 .OR.
335  $ min( r, g, ra ).LE.sfmin2 )GO TO 170
336  IF( disnan( c+f+ca+r+g+ra ) ) THEN
337 *
338 * Exit if NaN to avoid infinite loop
339 *
340  info = -3
341  CALL xerbla( 'ZGEBAL', -info )
342  RETURN
343  END IF
344  f = f*sclfac
345  c = c*sclfac
346  ca = ca*sclfac
347  r = r / sclfac
348  g = g / sclfac
349  ra = ra / sclfac
350  GO TO 160
351 *
352  170 CONTINUE
353  g = c / sclfac
354  180 CONTINUE
355  IF( g.LT.r .OR. max( r, ra ).GE.sfmax2 .OR.
356  $ min( f, c, g, ca ).LE.sfmin2 )GO TO 190
357  f = f / sclfac
358  c = c / sclfac
359  g = g / sclfac
360  ca = ca / sclfac
361  r = r*sclfac
362  ra = ra*sclfac
363  GO TO 180
364 *
365 * Now balance.
366 *
367  190 CONTINUE
368  IF( ( c+r ).GE.factor*s )
369  $ GO TO 200
370  IF( f.LT.one .AND. scale( i ).LT.one ) THEN
371  IF( f*scale( i ).LE.sfmin1 )
372  $ GO TO 200
373  END IF
374  IF( f.GT.one .AND. scale( i ).GT.one ) THEN
375  IF( scale( i ).GE.sfmax1 / f )
376  $ GO TO 200
377  END IF
378  g = one / f
379  scale( i ) = scale( i )*f
380  noconv = .true.
381 *
382  CALL zdscal( n-k+1, g, a( i, k ), lda )
383  CALL zdscal( l, f, a( 1, i ), 1 )
384 *
385  200 CONTINUE
386 *
387  IF( noconv )
388  $ GO TO 140
389 *
390  210 CONTINUE
391  ilo = k
392  ihi = l
393 *
394  RETURN
395 *
396 * End of ZGEBAL
397 *
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine zswap(N, ZX, INCX, ZY, INCY)
ZSWAP
Definition: zswap.f:52
integer function izamax(N, ZX, INCX)
IZAMAX
Definition: izamax.f:53
double precision function dznrm2(N, X, INCX)
DZNRM2
Definition: dznrm2.f:56
logical function disnan(DIN)
DISNAN tests input for NaN.
Definition: disnan.f:61
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine zdscal(N, DA, ZX, INCX)
ZDSCAL
Definition: zdscal.f:54

Here is the call graph for this function:

Here is the caller graph for this function: