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