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