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