LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zgbequb.f
Go to the documentation of this file.
1*> \brief \b ZGBEQUB
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZGBEQUB + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgbequb.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgbequb.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbequb.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZGBEQUB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
20* AMAX, INFO )
21*
22* .. Scalar Arguments ..
23* INTEGER INFO, KL, KU, LDAB, M, N
24* DOUBLE PRECISION AMAX, COLCND, ROWCND
25* ..
26* .. Array Arguments ..
27* DOUBLE PRECISION C( * ), R( * )
28* COMPLEX*16 AB( LDAB, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZGBEQUB computes row and column scalings intended to equilibrate an
38*> M-by-N matrix A and reduce its condition number. R returns the row
39*> scale factors and C the column scale factors, chosen to try to make
40*> the largest element in each row and column of the matrix B with
41*> elements B(i,j)=R(i)*A(i,j)*C(j) have an absolute value of at most
42*> the radix.
43*>
44*> R(i) and C(j) are restricted to be a power of the radix between
45*> SMLNUM = smallest safe number and BIGNUM = largest safe number. Use
46*> of these scaling factors is not guaranteed to reduce the condition
47*> number of A but works well in practice.
48*>
49*> This routine differs from ZGEEQU by restricting the scaling factors
50*> to a power of the radix. Barring over- and underflow, scaling by
51*> these factors introduces no additional rounding errors. However, the
52*> scaled entries' magnitudes are no longer approximately 1 but lie
53*> between sqrt(radix) and 1/sqrt(radix).
54*> \endverbatim
55*
56* Arguments:
57* ==========
58*
59*> \param[in] M
60*> \verbatim
61*> M is INTEGER
62*> The number of rows of the matrix A. M >= 0.
63*> \endverbatim
64*>
65*> \param[in] N
66*> \verbatim
67*> N is INTEGER
68*> The number of columns of the matrix A. N >= 0.
69*> \endverbatim
70*>
71*> \param[in] KL
72*> \verbatim
73*> KL is INTEGER
74*> The number of subdiagonals within the band of A. KL >= 0.
75*> \endverbatim
76*>
77*> \param[in] KU
78*> \verbatim
79*> KU is INTEGER
80*> The number of superdiagonals within the band of A. KU >= 0.
81*> \endverbatim
82*>
83*> \param[in] AB
84*> \verbatim
85*> AB is COMPLEX*16 array, dimension (LDAB,N)
86*> On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
87*> The j-th column of A is stored in the j-th column of the
88*> array AB as follows:
89*> AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
90*> \endverbatim
91*>
92*> \param[in] LDAB
93*> \verbatim
94*> LDAB is INTEGER
95*> The leading dimension of the array A. LDAB >= max(1,M).
96*> \endverbatim
97*>
98*> \param[out] R
99*> \verbatim
100*> R is DOUBLE PRECISION array, dimension (M)
101*> If INFO = 0 or INFO > M, R contains the row scale factors
102*> for A.
103*> \endverbatim
104*>
105*> \param[out] C
106*> \verbatim
107*> C is DOUBLE PRECISION array, dimension (N)
108*> If INFO = 0, C contains the column scale factors for A.
109*> \endverbatim
110*>
111*> \param[out] ROWCND
112*> \verbatim
113*> ROWCND is DOUBLE PRECISION
114*> If INFO = 0 or INFO > M, ROWCND contains the ratio of the
115*> smallest R(i) to the largest R(i). If ROWCND >= 0.1 and
116*> AMAX is neither too large nor too small, it is not worth
117*> scaling by R.
118*> \endverbatim
119*>
120*> \param[out] COLCND
121*> \verbatim
122*> COLCND is DOUBLE PRECISION
123*> If INFO = 0, COLCND contains the ratio of the smallest
124*> C(i) to the largest C(i). If COLCND >= 0.1, it is not
125*> worth scaling by C.
126*> \endverbatim
127*>
128*> \param[out] AMAX
129*> \verbatim
130*> AMAX is DOUBLE PRECISION
131*> Absolute value of largest matrix element. If AMAX is very
132*> close to overflow or very close to underflow, the matrix
133*> should be scaled.
134*> \endverbatim
135*>
136*> \param[out] INFO
137*> \verbatim
138*> INFO is INTEGER
139*> = 0: successful exit
140*> < 0: if INFO = -i, the i-th argument had an illegal value
141*> > 0: if INFO = i, and i is
142*> <= M: the i-th row of A is exactly zero
143*> > M: the (i-M)-th column of A is exactly zero
144*> \endverbatim
145*
146* Authors:
147* ========
148*
149*> \author Univ. of Tennessee
150*> \author Univ. of California Berkeley
151*> \author Univ. of Colorado Denver
152*> \author NAG Ltd.
153*
154*> \ingroup gbequb
155*
156* =====================================================================
157 SUBROUTINE zgbequb( M, N, KL, KU, AB, LDAB, R, C, ROWCND,
158 $ COLCND,
159 $ AMAX, INFO )
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*
346 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgbequb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)
ZGBEQUB
Definition zgbequb.f:160