LAPACK 3.12.1
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 157 of file zgbequb.f.

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