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

ZGBEQUB

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

Purpose:
 ZGBEQUB 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 ZGEEQU 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).
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 COMPLEX*16 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 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
June 2016

Definition at line 163 of file zgbequb.f.

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