3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZGEBAL + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgebal.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgebal.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgebal.f">
21 * SUBROUTINE ZGEBAL( JOB, N, A, LDA, ILO, IHI, SCALE, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER IHI, ILO, INFO, LDA, N
27 * .. Array Arguments ..
28 * DOUBLE PRECISION SCALE( * )
29 * COMPLEX*16 A( LDA, * )
38 *> ZGEBAL 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.
45 *> Balancing may reduce the 1-norm of the matrix, and improve the
46 *> accuracy of the computed eigenvalues and/or eigenvectors.
55 *> Specifies the operations to be performed on A:
56 *> = 'N': none: simply set ILO = 1, IHI = N, SCALE(I) = 1.0
58 *> = 'P': permute only;
60 *> = 'B': both permute and scale.
66 *> The order of the matrix A. N >= 0.
71 *> A is COMPLEX*16 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.
81 *> The leading dimension of the array A. LDA >= max(1,N).
90 *> ILO and IHI are set to INTEGER such that on exit
91 *> A(i,j) = 0 if i > j and j = 1,...,ILO-1 or I = IHI+1,...,N.
92 *> If JOB = 'N' or 'S', ILO = 1 and IHI = N.
97 *> SCALE is DOUBLE PRECISION array, dimension (N)
98 *> Details of the permutations and scaling factors applied to
99 *> A. If P(j) is the index of the row and column interchanged
100 *> with row and column j and D(j) is the scaling factor
101 *> applied to row and column j, then
102 *> SCALE(j) = P(j) for j = 1,...,ILO-1
103 *> = D(j) for j = ILO,...,IHI
104 *> = P(j) for j = IHI+1,...,N.
105 *> The order in which the interchanges are made is N to IHI+1,
112 *> = 0: successful exit.
113 *> < 0: if INFO = -i, the i-th argument had an illegal value.
119 *> \author Univ. of Tennessee
120 *> \author Univ. of California Berkeley
121 *> \author Univ. of Colorado Denver
124 *> \date November 2015
126 *> \ingroup complex16GEcomputational
128 *> \par Further Details:
129 * =====================
133 *> The permutations consist of row and column interchanges which put
134 *> the matrix in the form
140 *> where T1 and T2 are upper triangular matrices whose eigenvalues lie
141 *> along the diagonal. The column indices ILO and IHI mark the starting
142 *> and ending columns of the submatrix B. Balancing consists of applying
143 *> a diagonal similarity transformation inv(D) * B * D to make the
144 *> 1-norms of each row of B and its corresponding column nearly equal.
145 *> The output matrix is
148 *> ( 0 inv(D)*B*D inv(D)*Z ).
151 *> Information about the permutations P and the diagonal matrix D is
152 *> returned in the vector SCALE.
154 *> This subroutine is based on the EISPACK routine CBAL.
156 *> Modified by Tzu-Yi Chen, Computer Science Division, University of
157 *> California at Berkeley, USA
160 * =====================================================================
161 SUBROUTINE ZGEBAL( JOB, N, A, LDA, ILO, IHI, SCALE, INFO )
163 * -- LAPACK computational routine (version 3.6.0) --
164 * -- LAPACK is a software package provided by Univ. of Tennessee, --
165 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168 * .. Scalar Arguments ..
170 INTEGER IHI, ILO, INFO, LDA, N
172 * .. Array Arguments ..
173 DOUBLE PRECISION SCALE( * )
174 COMPLEX*16 A( LDA, * )
177 * =====================================================================
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 )
187 * .. Local Scalars ..
189 INTEGER I, ICA, IEXC, IRA, J, K, L, M
190 DOUBLE PRECISION C, CA, F, G, R, RA, S, SFMAX1, SFMAX2, SFMIN1,
194 * .. External Functions ..
195 LOGICAL DISNAN, LSAME
197 DOUBLE PRECISION DLAMCH, DZNRM2
198 EXTERNAL DISNAN, LSAME, IZAMAX, DLAMCH, DZNRM2
200 * .. External Subroutines ..
201 EXTERNAL XERBLA, ZDSCAL, ZSWAP
203 * .. Intrinsic Functions ..
204 INTRINSIC ABS, DBLE, DIMAG, MAX, MIN
206 * Test the input parameters
209 IF( .NOT.LSAME( JOB, 'N' ) .AND. .NOT.LSAME( JOB, 'P' ) .AND.
210 $ .NOT.LSAME( JOB, 'S' ) .AND. .NOT.LSAME( JOB, 'B' ) ) THEN
212 ELSE IF( N.LT.0 ) THEN
214 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
218 CALL XERBLA( 'ZGEBAL', -INFO )
228 IF( LSAME( JOB, 'N' ) ) THEN
235 IF( LSAME( JOB, 'S' ) )
238 * Permutation to isolate eigenvalues if possible
242 * Row and column exchange.
249 CALL ZSWAP( L, A( 1, J ), 1, A( 1, M ), 1 )
250 CALL ZSWAP( N-K+1, A( J, K ), LDA, A( M, K ), LDA )
255 * Search for rows isolating an eigenvalue and push them down.
268 IF( DBLE( A( J, I ) ).NE.ZERO .OR. DIMAG( A( J, I ) ).NE.
279 * Search for columns isolating an eigenvalue and push them left.
290 IF( DBLE( A( I, J ) ).NE.ZERO .OR. DIMAG( A( I, J ) ).NE.
304 IF( LSAME( JOB, 'P' ) )
307 * Balance the submatrix in rows K to L.
309 * Iterative loop for norm reduction
311 SFMIN1 = DLAMCH( 'S' ) / DLAMCH( 'P' )
312 SFMAX1 = ONE / SFMIN1
313 SFMIN2 = SFMIN1*SCLFAC
314 SFMAX2 = ONE / SFMIN2
320 C = DZNRM2( L-K+1, A( K, I ), 1 )
321 R = DZNRM2( L-K+1, A( I, K ), LDA )
322 ICA = IZAMAX( L, A( 1, I ), 1 )
323 CA = ABS( A( ICA, I ) )
324 IRA = IZAMAX( N-K+1, A( I, K ), LDA )
325 RA = ABS( A( I, IRA+K-1 ) )
327 * Guard against zero C or R due to underflow.
329 IF( C.EQ.ZERO .OR. R.EQ.ZERO )
335 IF( C.GE.G .OR. MAX( F, C, CA ).GE.SFMAX2 .OR.
336 $ MIN( R, G, RA ).LE.SFMIN2 )GO TO 170
337 IF( DISNAN( C+F+CA+R+G+RA ) ) THEN
339 * Exit if NaN to avoid infinite loop
342 CALL XERBLA( 'ZGEBAL', -INFO )
356 IF( G.LT.R .OR. MAX( R, RA ).GE.SFMAX2 .OR.
357 $ MIN( F, C, G, CA ).LE.SFMIN2 )GO TO 190
369 IF( ( C+R ).GE.FACTOR*S )
371 IF( F.LT.ONE .AND. SCALE( I ).LT.ONE ) THEN
372 IF( F*SCALE( I ).LE.SFMIN1 )
375 IF( F.GT.ONE .AND. SCALE( I ).GT.ONE ) THEN
376 IF( SCALE( I ).GE.SFMAX1 / F )
380 SCALE( I ) = SCALE( I )*F
383 CALL ZDSCAL( N-K+1, G, A( I, K ), LDA )
384 CALL ZDSCAL( L, F, A( 1, I ), 1 )