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

◆ sgbequ()

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

SGBEQU

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

Purpose:
 SGBEQU computes row and column scalings intended to equilibrate an
 M-by-N band 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]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)
          The band matrix A, stored 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(m,j+kl).
[in]LDAB
          LDAB is INTEGER
          The leading dimension of the array AB.  LDAB >= KL+KU+1.
[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 151 of file sgbequ.f.

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