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

DGEEQU

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

Purpose:
 DGEEQU 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 DOUBLE PRECISION 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 DOUBLE PRECISION array, dimension (M)
          If INFO = 0 or INFO > M, R contains the row scale factors
          for A.
[out]C
          C is DOUBLE PRECISION array, dimension (N)
          If INFO = 0,  C contains the column scale factors for A.
[out]ROWCND
          ROWCND is DOUBLE PRECISION
          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 DOUBLE PRECISION
          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 DOUBLE PRECISION
          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 141 of file dgeequ.f.

141 *
142 * -- LAPACK computational routine (version 3.4.0) --
143 * -- LAPACK is a software package provided by Univ. of Tennessee, --
144 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
145 * November 2011
146 *
147 * .. Scalar Arguments ..
148  INTEGER info, lda, m, n
149  DOUBLE PRECISION amax, colcnd, rowcnd
150 * ..
151 * .. Array Arguments ..
152  DOUBLE PRECISION a( lda, * ), c( * ), r( * )
153 * ..
154 *
155 * =====================================================================
156 *
157 * .. Parameters ..
158  DOUBLE PRECISION one, zero
159  parameter ( one = 1.0d+0, zero = 0.0d+0 )
160 * ..
161 * .. Local Scalars ..
162  INTEGER i, j
163  DOUBLE PRECISION bignum, rcmax, rcmin, smlnum
164 * ..
165 * .. External Functions ..
166  DOUBLE PRECISION dlamch
167  EXTERNAL dlamch
168 * ..
169 * .. External Subroutines ..
170  EXTERNAL xerbla
171 * ..
172 * .. Intrinsic Functions ..
173  INTRINSIC abs, max, min
174 * ..
175 * .. Executable Statements ..
176 *
177 * Test the input parameters.
178 *
179  info = 0
180  IF( m.LT.0 ) THEN
181  info = -1
182  ELSE IF( n.LT.0 ) THEN
183  info = -2
184  ELSE IF( lda.LT.max( 1, m ) ) THEN
185  info = -4
186  END IF
187  IF( info.NE.0 ) THEN
188  CALL xerbla( 'DGEEQU', -info )
189  RETURN
190  END IF
191 *
192 * Quick return if possible
193 *
194  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
195  rowcnd = one
196  colcnd = one
197  amax = zero
198  RETURN
199  END IF
200 *
201 * Get machine constants.
202 *
203  smlnum = dlamch( 'S' )
204  bignum = one / smlnum
205 *
206 * Compute row scale factors.
207 *
208  DO 10 i = 1, m
209  r( i ) = zero
210  10 CONTINUE
211 *
212 * Find the maximum element in each row.
213 *
214  DO 30 j = 1, n
215  DO 20 i = 1, m
216  r( i ) = max( r( i ), abs( a( i, j ) ) )
217  20 CONTINUE
218  30 CONTINUE
219 *
220 * Find the maximum and minimum scale factors.
221 *
222  rcmin = bignum
223  rcmax = zero
224  DO 40 i = 1, m
225  rcmax = max( rcmax, r( i ) )
226  rcmin = min( rcmin, r( i ) )
227  40 CONTINUE
228  amax = rcmax
229 *
230  IF( rcmin.EQ.zero ) THEN
231 *
232 * Find the first zero scale factor and return an error code.
233 *
234  DO 50 i = 1, m
235  IF( r( i ).EQ.zero ) THEN
236  info = i
237  RETURN
238  END IF
239  50 CONTINUE
240  ELSE
241 *
242 * Invert the scale factors.
243 *
244  DO 60 i = 1, m
245  r( i ) = one / min( max( r( i ), smlnum ), bignum )
246  60 CONTINUE
247 *
248 * Compute ROWCND = min(R(I)) / max(R(I))
249 *
250  rowcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
251  END IF
252 *
253 * Compute column scale factors
254 *
255  DO 70 j = 1, n
256  c( j ) = zero
257  70 CONTINUE
258 *
259 * Find the maximum element in each column,
260 * assuming the row scaling computed above.
261 *
262  DO 90 j = 1, n
263  DO 80 i = 1, m
264  c( j ) = max( c( j ), abs( a( i, j ) )*r( i ) )
265  80 CONTINUE
266  90 CONTINUE
267 *
268 * Find the maximum and minimum scale factors.
269 *
270  rcmin = bignum
271  rcmax = zero
272  DO 100 j = 1, n
273  rcmin = min( rcmin, c( j ) )
274  rcmax = max( rcmax, c( j ) )
275  100 CONTINUE
276 *
277  IF( rcmin.EQ.zero ) THEN
278 *
279 * Find the first zero scale factor and return an error code.
280 *
281  DO 110 j = 1, n
282  IF( c( j ).EQ.zero ) THEN
283  info = m + j
284  RETURN
285  END IF
286  110 CONTINUE
287  ELSE
288 *
289 * Invert the scale factors.
290 *
291  DO 120 j = 1, n
292  c( j ) = one / min( max( c( j ), smlnum ), bignum )
293  120 CONTINUE
294 *
295 * Compute COLCND = min(C(J)) / max(C(J))
296 *
297  colcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
298  END IF
299 *
300  RETURN
301 *
302 * End of DGEEQU
303 *
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62

Here is the call graph for this function:

Here is the caller graph for this function: