LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
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 *> \htmlonly
9 *> Download ZGEEQU + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgeequ.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgeequ.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeequ.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZGEEQU( M, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, M, N
26 * DOUBLE PRECISION AMAX, COLCND, ROWCND
27 * ..
28 * .. Array Arguments ..
29 * DOUBLE PRECISION C( * ), R( * )
30 * COMPLEX*16 A( LDA, * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> ZGEEQU 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*16 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION
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 DOUBLE PRECISION
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 DOUBLE PRECISION
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 *> \date November 2011
136 *
137 *> \ingroup complex16GEcomputational
138 *
139 * =====================================================================
140  SUBROUTINE zgeequ( M, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
141  $ info )
142 *
143 * -- LAPACK computational routine (version 3.4.0) --
144 * -- LAPACK is a software package provided by Univ. of Tennessee, --
145 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146 * November 2011
147 *
148 * .. Scalar Arguments ..
149  INTEGER info, lda, m, n
150  DOUBLE PRECISION amax, colcnd, rowcnd
151 * ..
152 * .. Array Arguments ..
153  DOUBLE PRECISION c( * ), r( * )
154  COMPLEX*16 a( lda, * )
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
166  COMPLEX*16 zdum
167 * ..
168 * .. External Functions ..
169  DOUBLE PRECISION dlamch
170  EXTERNAL dlamch
171 * ..
172 * .. External Subroutines ..
173  EXTERNAL xerbla
174 * ..
175 * .. Intrinsic Functions ..
176  INTRINSIC abs, dble, dimag, max, min
177 * ..
178 * .. Statement Functions ..
179  DOUBLE PRECISION cabs1
180 * ..
181 * .. Statement Function definitions ..
182  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
183 * ..
184 * .. Executable Statements ..
185 *
186 * Test the input parameters.
187 *
188  info = 0
189  IF( m.LT.0 ) THEN
190  info = -1
191  ELSE IF( n.LT.0 ) THEN
192  info = -2
193  ELSE IF( lda.LT.max( 1, m ) ) THEN
194  info = -4
195  END IF
196  IF( info.NE.0 ) THEN
197  CALL xerbla( 'ZGEEQU', -info )
198  return
199  END IF
200 *
201 * Quick return if possible
202 *
203  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
204  rowcnd = one
205  colcnd = one
206  amax = zero
207  return
208  END IF
209 *
210 * Get machine constants.
211 *
212  smlnum = dlamch( 'S' )
213  bignum = one / smlnum
214 *
215 * Compute row scale factors.
216 *
217  DO 10 i = 1, m
218  r( i ) = zero
219  10 continue
220 *
221 * Find the maximum element in each row.
222 *
223  DO 30 j = 1, n
224  DO 20 i = 1, m
225  r( i ) = max( r( i ), cabs1( a( i, j ) ) )
226  20 continue
227  30 continue
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 ), cabs1( a( i, j ) )*r( i ) )
274  80 continue
275  90 continue
276 *
277 * Find the maximum and minimum scale factors.
278 *
279  rcmin = bignum
280  rcmax = zero
281  DO 100 j = 1, n
282  rcmin = min( rcmin, c( j ) )
283  rcmax = max( rcmax, c( j ) )
284  100 continue
285 *
286  IF( rcmin.EQ.zero ) THEN
287 *
288 * Find the first zero scale factor and return an error code.
289 *
290  DO 110 j = 1, n
291  IF( c( j ).EQ.zero ) THEN
292  info = m + j
293  return
294  END IF
295  110 continue
296  ELSE
297 *
298 * Invert the scale factors.
299 *
300  DO 120 j = 1, n
301  c( j ) = one / min( max( c( j ), smlnum ), bignum )
302  120 continue
303 *
304 * Compute COLCND = min(C(J)) / max(C(J))
305 *
306  colcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
307  END IF
308 *
309  return
310 *
311 * End of ZGEEQU
312 *
313  END