LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sgeequb.f
Go to the documentation of this file.
1 *> \brief \b SGEEQUB
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SGEEQUB + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgeequb.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgeequb.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgeequb.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SGEEQUB( M, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, M, N
26 * REAL AMAX, COLCND, ROWCND
27 * ..
28 * .. Array Arguments ..
29 * REAL A( LDA, * ), C( * ), R( * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> SGEEQUB computes row and column scalings intended to equilibrate an
39 *> M-by-N matrix A and reduce its condition number. R returns the row
40 *> scale factors and C the column scale factors, chosen to try to make
41 *> the largest element in each row and column of the matrix B with
42 *> elements B(i,j)=R(i)*A(i,j)*C(j) have an absolute value of at most
43 *> the radix.
44 *>
45 *> R(i) and C(j) are restricted to be a power of the radix between
46 *> SMLNUM = smallest safe number and BIGNUM = largest safe number. Use
47 *> of these scaling factors is not guaranteed to reduce the condition
48 *> number of A but works well in practice.
49 *>
50 *> This routine differs from SGEEQU by restricting the scaling factors
51 *> to a power of the radix. Baring over- and underflow, scaling by
52 *> these factors introduces no additional rounding errors. However, the
53 *> scaled entries' magnitured are no longer approximately 1 but lie
54 *> between sqrt(radix) and 1/sqrt(radix).
55 *> \endverbatim
56 *
57 * Arguments:
58 * ==========
59 *
60 *> \param[in] M
61 *> \verbatim
62 *> M is INTEGER
63 *> The number of rows of the matrix A. M >= 0.
64 *> \endverbatim
65 *>
66 *> \param[in] N
67 *> \verbatim
68 *> N is INTEGER
69 *> The number of columns of the matrix A. N >= 0.
70 *> \endverbatim
71 *>
72 *> \param[in] A
73 *> \verbatim
74 *> A is REAL array, dimension (LDA,N)
75 *> The M-by-N matrix whose equilibration factors are
76 *> to be computed.
77 *> \endverbatim
78 *>
79 *> \param[in] LDA
80 *> \verbatim
81 *> LDA is INTEGER
82 *> The leading dimension of the array A. LDA >= max(1,M).
83 *> \endverbatim
84 *>
85 *> \param[out] R
86 *> \verbatim
87 *> R is REAL array, dimension (M)
88 *> If INFO = 0 or INFO > M, R contains the row scale factors
89 *> for A.
90 *> \endverbatim
91 *>
92 *> \param[out] C
93 *> \verbatim
94 *> C is REAL array, dimension (N)
95 *> If INFO = 0, C contains the column scale factors for A.
96 *> \endverbatim
97 *>
98 *> \param[out] ROWCND
99 *> \verbatim
100 *> ROWCND is REAL
101 *> If INFO = 0 or INFO > M, ROWCND contains the ratio of the
102 *> smallest R(i) to the largest R(i). If ROWCND >= 0.1 and
103 *> AMAX is neither too large nor too small, it is not worth
104 *> scaling by R.
105 *> \endverbatim
106 *>
107 *> \param[out] COLCND
108 *> \verbatim
109 *> COLCND is REAL
110 *> If INFO = 0, COLCND contains the ratio of the smallest
111 *> C(i) to the largest C(i). If COLCND >= 0.1, it is not
112 *> worth scaling by C.
113 *> \endverbatim
114 *>
115 *> \param[out] AMAX
116 *> \verbatim
117 *> AMAX is REAL
118 *> Absolute value of largest matrix element. If AMAX is very
119 *> close to overflow or very close to underflow, the matrix
120 *> should be scaled.
121 *> \endverbatim
122 *>
123 *> \param[out] INFO
124 *> \verbatim
125 *> INFO is INTEGER
126 *> = 0: successful exit
127 *> < 0: if INFO = -i, the i-th argument had an illegal value
128 *> > 0: if INFO = i, and i is
129 *> <= M: the i-th row of A is exactly zero
130 *> > M: the (i-M)-th column of A is exactly zero
131 *> \endverbatim
132 *
133 * Authors:
134 * ========
135 *
136 *> \author Univ. of Tennessee
137 *> \author Univ. of California Berkeley
138 *> \author Univ. of Colorado Denver
139 *> \author NAG Ltd.
140 *
141 *> \date November 2011
142 *
143 *> \ingroup realGEcomputational
144 *
145 * =====================================================================
146  SUBROUTINE sgeequb( M, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
147  $ info )
148 *
149 * -- LAPACK computational routine (version 3.4.0) --
150 * -- LAPACK is a software package provided by Univ. of Tennessee, --
151 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
152 * November 2011
153 *
154 * .. Scalar Arguments ..
155  INTEGER INFO, LDA, M, N
156  REAL AMAX, COLCND, ROWCND
157 * ..
158 * .. Array Arguments ..
159  REAL A( lda, * ), C( * ), R( * )
160 * ..
161 *
162 * =====================================================================
163 *
164 * .. Parameters ..
165  REAL ONE, ZERO
166  parameter ( one = 1.0e+0, zero = 0.0e+0 )
167 * ..
168 * .. Local Scalars ..
169  INTEGER I, J
170  REAL BIGNUM, RCMAX, RCMIN, SMLNUM, RADIX, LOGRDX
171 * ..
172 * .. External Functions ..
173  REAL SLAMCH
174  EXTERNAL slamch
175 * ..
176 * .. External Subroutines ..
177  EXTERNAL xerbla
178 * ..
179 * .. Intrinsic Functions ..
180  INTRINSIC abs, max, min, log
181 * ..
182 * .. Executable Statements ..
183 *
184 * Test the input parameters.
185 *
186  info = 0
187  IF( m.LT.0 ) THEN
188  info = -1
189  ELSE IF( n.LT.0 ) THEN
190  info = -2
191  ELSE IF( lda.LT.max( 1, m ) ) THEN
192  info = -4
193  END IF
194  IF( info.NE.0 ) THEN
195  CALL xerbla( 'SGEEQUB', -info )
196  RETURN
197  END IF
198 *
199 * Quick return if possible.
200 *
201  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
202  rowcnd = one
203  colcnd = one
204  amax = zero
205  RETURN
206  END IF
207 *
208 * Get machine constants. Assume SMLNUM is a power of the radix.
209 *
210  smlnum = slamch( 'S' )
211  bignum = one / smlnum
212  radix = slamch( 'B' )
213  logrdx = log( radix )
214 *
215 * Compute row scale factors.
216 *
217  DO 10 i = 1, m
218  r( i ) = zero
219  10 CONTINUE
220 *
221 * Find the maximum element in each row.
222 *
223  DO 30 j = 1, n
224  DO 20 i = 1, m
225  r( i ) = max( r( i ), abs( a( i, j ) ) )
226  20 CONTINUE
227  30 CONTINUE
228  DO i = 1, m
229  IF( r( i ).GT.zero ) THEN
230  r( i ) = radix**int( log( r( i ) ) / logrdx )
231  END IF
232  END DO
233 *
234 * Find the maximum and minimum scale factors.
235 *
236  rcmin = bignum
237  rcmax = zero
238  DO 40 i = 1, m
239  rcmax = max( rcmax, r( i ) )
240  rcmin = min( rcmin, r( i ) )
241  40 CONTINUE
242  amax = rcmax
243 *
244  IF( rcmin.EQ.zero ) THEN
245 *
246 * Find the first zero scale factor and return an error code.
247 *
248  DO 50 i = 1, m
249  IF( r( i ).EQ.zero ) THEN
250  info = i
251  RETURN
252  END IF
253  50 CONTINUE
254  ELSE
255 *
256 * Invert the scale factors.
257 *
258  DO 60 i = 1, m
259  r( i ) = one / min( max( r( i ), smlnum ), bignum )
260  60 CONTINUE
261 *
262 * Compute ROWCND = min(R(I)) / max(R(I)).
263 *
264  rowcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
265  END IF
266 *
267 * Compute column scale factors
268 *
269  DO 70 j = 1, n
270  c( j ) = zero
271  70 CONTINUE
272 *
273 * Find the maximum element in each column,
274 * assuming the row scaling computed above.
275 *
276  DO 90 j = 1, n
277  DO 80 i = 1, m
278  c( j ) = max( c( j ), abs( a( i, j ) )*r( i ) )
279  80 CONTINUE
280  IF( c( j ).GT.zero ) THEN
281  c( j ) = radix**int( log( c( j ) ) / logrdx )
282  END IF
283  90 CONTINUE
284 *
285 * Find the maximum and minimum scale factors.
286 *
287  rcmin = bignum
288  rcmax = zero
289  DO 100 j = 1, n
290  rcmin = min( rcmin, c( j ) )
291  rcmax = max( rcmax, c( j ) )
292  100 CONTINUE
293 *
294  IF( rcmin.EQ.zero ) THEN
295 *
296 * Find the first zero scale factor and return an error code.
297 *
298  DO 110 j = 1, n
299  IF( c( j ).EQ.zero ) THEN
300  info = m + j
301  RETURN
302  END IF
303  110 CONTINUE
304  ELSE
305 *
306 * Invert the scale factors.
307 *
308  DO 120 j = 1, n
309  c( j ) = one / min( max( c( j ), smlnum ), bignum )
310  120 CONTINUE
311 *
312 * Compute COLCND = min(C(J)) / max(C(J)).
313 *
314  colcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
315  END IF
316 *
317  RETURN
318 *
319 * End of SGEEQUB
320 *
321  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine sgeequb(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)
SGEEQUB
Definition: sgeequb.f:148