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