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

◆ zgbequb()

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.  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 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.

Definition at line 159 of file zgbequb.f.

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