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