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

◆ sgbequb()

subroutine sgbequb ( integer m,
integer n,
integer kl,
integer ku,
real, dimension( ldab, * ) ab,
integer ldab,
real, dimension( * ) r,
real, dimension( * ) c,
real rowcnd,
real colcnd,
real amax,
integer info )

SGBEQUB

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

Purpose:
!>
!> SGBEQUB 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 SGEEQU 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]KL
!>          KL is INTEGER
!>          The number of subdiagonals within the band of A.  KL >= 0.
!> 
[in]KU
!>          KU is INTEGER
!>          The number of superdiagonals within the band of A.  KU >= 0.
!> 
[in]AB
!>          AB is REAL array, dimension (LDAB,N)
!>          On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
!>          The j-th column of A is stored in the j-th column of the
!>          array AB as follows:
!>          AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
!> 
[in]LDAB
!>          LDAB is INTEGER
!>          The leading dimension of the array A.  LDAB >= 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 156 of file sgbequb.f.

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