LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dgbequ ( integer  M,
integer  N,
integer  KL,
integer  KU,
double precision, dimension( ldab, * )  AB,
integer  LDAB,
double precision, dimension( * )  R,
double precision, dimension( * )  C,
double precision  ROWCND,
double precision  COLCND,
double precision  AMAX,
integer  INFO 
)

DGBEQU

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

Purpose:
 DGBEQU 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 DOUBLE PRECISION 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 DOUBLE PRECISION array, dimension (M)
          If INFO = 0, or INFO > M, R contains the row scale factors
          for A.
[out]C
          C is DOUBLE PRECISION array, dimension (N)
          If INFO = 0, C contains the column scale factors for A.
[out]ROWCND
          ROWCND is DOUBLE PRECISION
          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 DOUBLE PRECISION
          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 DOUBLE PRECISION
          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.
Date
November 2011

Definition at line 155 of file dgbequ.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: