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

SGEEQUB

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

Purpose:
 SGEEQUB 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 SGEEQU 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 REAL 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 148 of file sgeequb.f.

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