summaryrefslogtreecommitdiff
path: root/SRC/cgeequb.f
diff options
context:
space:
mode:
authorjulie <julielangou@users.noreply.github.com>2008-12-16 17:06:58 +0000
committerjulie <julielangou@users.noreply.github.com>2008-12-16 17:06:58 +0000
commitff981f106bde4ce6a74aa4f4a572c943f5a395b2 (patch)
treea386cad907bcaefd6893535c31d67ec9468e693e /SRC/cgeequb.f
parente58b61578b55644f6391f3333262b72c1dc88437 (diff)
downloadlapack-ff981f106bde4ce6a74aa4f4a572c943f5a395b2.tar.gz
lapack-ff981f106bde4ce6a74aa4f4a572c943f5a395b2.tar.bz2
lapack-ff981f106bde4ce6a74aa4f4a572c943f5a395b2.zip
Diffstat (limited to 'SRC/cgeequb.f')
-rw-r--r--SRC/cgeequb.f256
1 files changed, 256 insertions, 0 deletions
diff --git a/SRC/cgeequb.f b/SRC/cgeequb.f
new file mode 100644
index 00000000..b8dd2dd5
--- /dev/null
+++ b/SRC/cgeequb.f
@@ -0,0 +1,256 @@
+ SUBROUTINE CGEEQUB( M, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
+ $ INFO )
+*
+* -- LAPACK routine (version 3.2) --
+* -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --
+* -- Jason Riedy of Univ. of California Berkeley. --
+* -- November 2008 --
+*
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley and NAG Ltd. --
+*
+ IMPLICIT NONE
+* ..
+* .. Scalar Arguments ..
+ INTEGER INFO, LDA, M, N
+ REAL AMAX, COLCND, ROWCND
+* ..
+* .. Array Arguments ..
+ REAL C( * ), R( * )
+ COMPLEX A( LDA, * )
+* ..
+*
+* 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).
+*
+* Arguments
+* =========
+*
+* M (input) INTEGER
+* The number of rows of the matrix A. M >= 0.
+*
+* N (input) INTEGER
+* The number of columns of the matrix A. N >= 0.
+*
+* A (input) COMPLEX array, dimension (LDA,N)
+* The M-by-N matrix whose equilibration factors are
+* to be computed.
+*
+* LDA (input) INTEGER
+* The leading dimension of the array A. LDA >= max(1,M).
+*
+* R (output) REAL array, dimension (M)
+* If INFO = 0 or INFO > M, R contains the row scale factors
+* for A.
+*
+* C (output) REAL array, dimension (N)
+* If INFO = 0, C contains the column scale factors for A.
+*
+* ROWCND (output) 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.
+*
+* COLCND (output) 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.
+*
+* AMAX (output) REAL
+* Absolute value of largest matrix element. If AMAX is very
+* close to overflow or very close to underflow, the matrix
+* should be scaled.
+*
+* INFO (output) 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
+*
+* =====================================================================
+*
+* .. Parameters ..
+ REAL ONE, ZERO
+ PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
+* ..
+* .. Local Scalars ..
+ INTEGER I, J
+ REAL BIGNUM, RCMAX, RCMIN, SMLNUM, RADIX, LOGRDX
+ COMPLEX ZDUM
+* ..
+* .. External Functions ..
+ REAL SLAMCH
+ EXTERNAL SLAMCH
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC ABS, MAX, MIN, LOG, REAL, AIMAG
+* ..
+* .. Statement Functions ..
+ REAL CABS1
+* ..
+* .. Statement Function definitions ..
+ CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
+* ..
+* .. Executable Statements ..
+*
+* Test the input parameters.
+*
+ INFO = 0
+ IF( M.LT.0 ) THEN
+ INFO = -1
+ ELSE IF( N.LT.0 ) THEN
+ INFO = -2
+ ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
+ INFO = -4
+ END IF
+ IF( INFO.NE.0 ) THEN
+ CALL XERBLA( 'CGEEQUB', -INFO )
+ RETURN
+ END IF
+*
+* Quick return if possible.
+*
+ IF( M.EQ.0 .OR. N.EQ.0 ) THEN
+ ROWCND = ONE
+ COLCND = ONE
+ AMAX = ZERO
+ RETURN
+ END IF
+*
+* Get machine constants. Assume SMLNUM is a power of the radix.
+*
+ SMLNUM = SLAMCH( 'S' )
+ BIGNUM = ONE / SMLNUM
+ RADIX = SLAMCH( 'B' )
+ LOGRDX = LOG( RADIX )
+*
+* Compute row scale factors.
+*
+ DO 10 I = 1, M
+ R( I ) = ZERO
+ 10 CONTINUE
+*
+* Find the maximum element in each row.
+*
+ DO 30 J = 1, N
+ DO 20 I = 1, M
+ R( I ) = MAX( R( I ), CABS1( A( I, J ) ) )
+ 20 CONTINUE
+ 30 CONTINUE
+ DO I = 1, M
+ IF( R( I ).GT.ZERO ) THEN
+ R( I ) = RADIX**INT( LOG(R( I ) ) / LOGRDX )
+ END IF
+ END DO
+*
+* Find the maximum and minimum scale factors.
+*
+ RCMIN = BIGNUM
+ RCMAX = ZERO
+ DO 40 I = 1, M
+ RCMAX = MAX( RCMAX, R( I ) )
+ RCMIN = MIN( RCMIN, R( I ) )
+ 40 CONTINUE
+ AMAX = RCMAX
+*
+ IF( RCMIN.EQ.ZERO ) THEN
+*
+* Find the first zero scale factor and return an error code.
+*
+ DO 50 I = 1, M
+ IF( R( I ).EQ.ZERO ) THEN
+ INFO = I
+ RETURN
+ END IF
+ 50 CONTINUE
+ ELSE
+*
+* Invert the scale factors.
+*
+ DO 60 I = 1, M
+ R( I ) = ONE / MIN( MAX( R( I ), SMLNUM ), BIGNUM )
+ 60 CONTINUE
+*
+* Compute ROWCND = min(R(I)) / max(R(I)).
+*
+ ROWCND = MAX( RCMIN, SMLNUM ) / MIN( RCMAX, BIGNUM )
+ END IF
+*
+* Compute column scale factors.
+*
+ DO 70 J = 1, N
+ C( J ) = ZERO
+ 70 CONTINUE
+*
+* Find the maximum element in each column,
+* assuming the row scaling computed above.
+*
+ DO 90 J = 1, N
+ DO 80 I = 1, M
+ C( J ) = MAX( C( J ), CABS1( A( I, J ) )*R( I ) )
+ 80 CONTINUE
+ IF( C( J ).GT.ZERO ) THEN
+ C( J ) = RADIX**INT( LOG( C( J ) ) / LOGRDX )
+ END IF
+ 90 CONTINUE
+*
+* Find the maximum and minimum scale factors.
+*
+ RCMIN = BIGNUM
+ RCMAX = ZERO
+ DO 100 J = 1, N
+ RCMIN = MIN( RCMIN, C( J ) )
+ RCMAX = MAX( RCMAX, C( J ) )
+ 100 CONTINUE
+*
+ IF( RCMIN.EQ.ZERO ) THEN
+*
+* Find the first zero scale factor and return an error code.
+*
+ DO 110 J = 1, N
+ IF( C( J ).EQ.ZERO ) THEN
+ INFO = M + J
+ RETURN
+ END IF
+ 110 CONTINUE
+ ELSE
+*
+* Invert the scale factors.
+*
+ DO 120 J = 1, N
+ C( J ) = ONE / MIN( MAX( C( J ), SMLNUM ), BIGNUM )
+ 120 CONTINUE
+*
+* Compute COLCND = min(C(J)) / max(C(J)).
+*
+ COLCND = MAX( RCMIN, SMLNUM ) / MIN( RCMAX, BIGNUM )
+ END IF
+*
+ RETURN
+*
+* End of CGEEQUB
+*
+ END