LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cgeequ ( integer  M,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  R,
real, dimension( * )  C,
real  ROWCND,
real  COLCND,
real  AMAX,
integer  INFO 
)

CGEEQU

Download CGEEQU + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 CGEEQU computes row and column scalings intended to equilibrate an
 M-by-N matrix A and reduce its condition number.  R returns the row
 scale factors and C the column scale factors, chosen to try to make
 the largest element in each row and column of the matrix B with
 elements B(i,j)=R(i)*A(i,j)*C(j) have absolute value 1.

 R(i) and C(j) are restricted to be between SMLNUM = smallest safe
 number and BIGNUM = largest safe number.  Use of these scaling
 factors is not guaranteed to reduce the condition number of A but
 works well in practice.
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrix A.  M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix A.  N >= 0.
[in]A
          A is COMPLEX array, dimension (LDA,N)
          The M-by-N matrix whose equilibration factors are
          to be computed.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,M).
[out]R
          R is REAL array, dimension (M)
          If INFO = 0 or INFO > M, R contains the row scale factors
          for A.
[out]C
          C is REAL array, dimension (N)
          If INFO = 0,  C contains the column scale factors for A.
[out]ROWCND
          ROWCND is REAL
          If INFO = 0 or INFO > M, ROWCND contains the ratio of the
          smallest R(i) to the largest R(i).  If ROWCND >= 0.1 and
          AMAX is neither too large nor too small, it is not worth
          scaling by R.
[out]COLCND
          COLCND is REAL
          If INFO = 0, COLCND contains the ratio of the smallest
          C(i) to the largest C(i).  If COLCND >= 0.1, it is not
          worth scaling by C.
[out]AMAX
          AMAX is REAL
          Absolute value of largest matrix element.  If AMAX is very
          close to overflow or very close to underflow, the matrix
          should be scaled.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
          > 0:  if INFO = i,  and i is
                <= M:  the i-th row of A is exactly zero
                >  M:  the (i-M)-th column of A is exactly zero
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 142 of file cgeequ.f.

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  REAL amax, colcnd, rowcnd
151 * ..
152 * .. Array Arguments ..
153  REAL c( * ), r( * )
154  COMPLEX a( lda, * )
155 * ..
156 *
157 * =====================================================================
158 *
159 * .. Parameters ..
160  REAL one, zero
161  parameter ( one = 1.0e+0, zero = 0.0e+0 )
162 * ..
163 * .. Local Scalars ..
164  INTEGER i, j
165  REAL bignum, rcmax, rcmin, smlnum
166  COMPLEX zdum
167 * ..
168 * .. External Functions ..
169  REAL slamch
170  EXTERNAL slamch
171 * ..
172 * .. External Subroutines ..
173  EXTERNAL xerbla
174 * ..
175 * .. Intrinsic Functions ..
176  INTRINSIC abs, aimag, max, min, real
177 * ..
178 * .. Statement Functions ..
179  REAL cabs1
180 * ..
181 * .. Statement Function definitions ..
182  cabs1( zdum ) = abs( REAL( ZDUM ) ) + abs( aimag( 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( 'CGEEQU', -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 = slamch( '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 CGEEQU
312 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69

Here is the call graph for this function:

Here is the caller graph for this function: