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