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

CGEEQUB

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

Purpose:
 CGEEQUB 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 an absolute value of at most
 the radix.

 R(i) and C(j) are restricted to be a power of the radix 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.

 This routine differs from CGEEQU by restricting the scaling factors
 to a power of the radix.  Baring over- and underflow, scaling by
 these factors introduces no additional rounding errors.  However, the
 scaled entries' magnitured are no longer approximately 1 but lie
 between sqrt(radix) and 1/sqrt(radix).
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 149 of file cgeequb.f.

149 *
150 * -- LAPACK computational routine (version 3.4.0) --
151 * -- LAPACK is a software package provided by Univ. of Tennessee, --
152 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153 * November 2011
154 *
155 * .. Scalar Arguments ..
156  INTEGER info, lda, m, n
157  REAL amax, colcnd, rowcnd
158 * ..
159 * .. Array Arguments ..
160  REAL c( * ), r( * )
161  COMPLEX a( lda, * )
162 * ..
163 *
164 * =====================================================================
165 *
166 * .. Parameters ..
167  REAL one, zero
168  parameter ( one = 1.0e+0, zero = 0.0e+0 )
169 * ..
170 * .. Local Scalars ..
171  INTEGER i, j
172  REAL bignum, rcmax, rcmin, smlnum, radix, logrdx
173  COMPLEX zdum
174 * ..
175 * .. External Functions ..
176  REAL slamch
177  EXTERNAL slamch
178 * ..
179 * .. External Subroutines ..
180  EXTERNAL xerbla
181 * ..
182 * .. Intrinsic Functions ..
183  INTRINSIC abs, max, min, log, REAL, aimag
184 * ..
185 * .. Statement Functions ..
186  REAL cabs1
187 * ..
188 * .. Statement Function definitions ..
189  cabs1( zdum ) = abs( REAL( ZDUM ) ) + abs( aimag( zdum ) )
190 * ..
191 * .. Executable Statements ..
192 *
193 * Test the input parameters.
194 *
195  info = 0
196  IF( m.LT.0 ) THEN
197  info = -1
198  ELSE IF( n.LT.0 ) THEN
199  info = -2
200  ELSE IF( lda.LT.max( 1, m ) ) THEN
201  info = -4
202  END IF
203  IF( info.NE.0 ) THEN
204  CALL xerbla( 'CGEEQUB', -info )
205  RETURN
206  END IF
207 *
208 * Quick return if possible.
209 *
210  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
211  rowcnd = one
212  colcnd = one
213  amax = zero
214  RETURN
215  END IF
216 *
217 * Get machine constants. Assume SMLNUM is a power of the radix.
218 *
219  smlnum = slamch( 'S' )
220  bignum = one / smlnum
221  radix = slamch( 'B' )
222  logrdx = log( radix )
223 *
224 * Compute row scale factors.
225 *
226  DO 10 i = 1, m
227  r( i ) = zero
228  10 CONTINUE
229 *
230 * Find the maximum element in each row.
231 *
232  DO 30 j = 1, n
233  DO 20 i = 1, m
234  r( i ) = max( r( i ), cabs1( a( i, j ) ) )
235  20 CONTINUE
236  30 CONTINUE
237  DO i = 1, m
238  IF( r( i ).GT.zero ) THEN
239  r( i ) = radix**int( log(r( i ) ) / logrdx )
240  END IF
241  END DO
242 *
243 * Find the maximum and minimum scale factors.
244 *
245  rcmin = bignum
246  rcmax = zero
247  DO 40 i = 1, m
248  rcmax = max( rcmax, r( i ) )
249  rcmin = min( rcmin, r( i ) )
250  40 CONTINUE
251  amax = rcmax
252 *
253  IF( rcmin.EQ.zero ) THEN
254 *
255 * Find the first zero scale factor and return an error code.
256 *
257  DO 50 i = 1, m
258  IF( r( i ).EQ.zero ) THEN
259  info = i
260  RETURN
261  END IF
262  50 CONTINUE
263  ELSE
264 *
265 * Invert the scale factors.
266 *
267  DO 60 i = 1, m
268  r( i ) = one / min( max( r( i ), smlnum ), bignum )
269  60 CONTINUE
270 *
271 * Compute ROWCND = min(R(I)) / max(R(I)).
272 *
273  rowcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
274  END IF
275 *
276 * Compute column scale factors.
277 *
278  DO 70 j = 1, n
279  c( j ) = zero
280  70 CONTINUE
281 *
282 * Find the maximum element in each column,
283 * assuming the row scaling computed above.
284 *
285  DO 90 j = 1, n
286  DO 80 i = 1, m
287  c( j ) = max( c( j ), cabs1( a( i, j ) )*r( i ) )
288  80 CONTINUE
289  IF( c( j ).GT.zero ) THEN
290  c( j ) = radix**int( log( c( j ) ) / logrdx )
291  END IF
292  90 CONTINUE
293 *
294 * Find the maximum and minimum scale factors.
295 *
296  rcmin = bignum
297  rcmax = zero
298  DO 100 j = 1, n
299  rcmin = min( rcmin, c( j ) )
300  rcmax = max( rcmax, c( j ) )
301  100 CONTINUE
302 *
303  IF( rcmin.EQ.zero ) THEN
304 *
305 * Find the first zero scale factor and return an error code.
306 *
307  DO 110 j = 1, n
308  IF( c( j ).EQ.zero ) THEN
309  info = m + j
310  RETURN
311  END IF
312  110 CONTINUE
313  ELSE
314 *
315 * Invert the scale factors.
316 *
317  DO 120 j = 1, n
318  c( j ) = one / min( max( c( j ), smlnum ), bignum )
319  120 CONTINUE
320 *
321 * Compute COLCND = min(C(J)) / max(C(J)).
322 *
323  colcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
324  END IF
325 *
326  RETURN
327 *
328 * End of CGEEQUB
329 *
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: