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

◆ cgeequb()

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.  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 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.

Definition at line 143 of file cgeequb.f.

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