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

◆ sgeequ()

subroutine sgeequ ( integer  m,
integer  n,
real, dimension( lda, * )  a,
integer  lda,
real, dimension( * )  r,
real, dimension( * )  c,
real  rowcnd,
real  colcnd,
real  amax,
integer  info 
)

SGEEQU

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

Purpose:
 SGEEQU 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 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.

Definition at line 137 of file sgeequ.f.

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