LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dgeequb()

subroutine dgeequb ( 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 
)

DGEEQUB

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

Purpose:
 DGEEQUB 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 DGEEQU by restricting the scaling factors
 to a power of the radix.  Barring over- and underflow, scaling by
 these factors introduces no additional rounding errors.  However, the
 scaled entries' magnitudes 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 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.

Definition at line 144 of file dgeequb.f.

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