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