LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dgbequb.f
Go to the documentation of this file.
1*> \brief \b DGBEQUB
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download DGBEQUB + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgbequb.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgbequb.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgbequb.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE DGBEQUB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
22* AMAX, INFO )
23*
24* .. Scalar Arguments ..
25* INTEGER INFO, KL, KU, LDAB, M, N
26* DOUBLE PRECISION AMAX, COLCND, ROWCND
27* ..
28* .. Array Arguments ..
29* DOUBLE PRECISION AB( LDAB, * ), C( * ), R( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> DGBEQUB computes row and column scalings intended to equilibrate an
39*> M-by-N matrix A and reduce its condition number. R returns the row
40*> scale factors and C the column scale factors, chosen to try to make
41*> the largest element in each row and column of the matrix B with
42*> elements B(i,j)=R(i)*A(i,j)*C(j) have an absolute value of at most
43*> the radix.
44*>
45*> R(i) and C(j) are restricted to be a power of the radix between
46*> SMLNUM = smallest safe number and BIGNUM = largest safe number. Use
47*> of these scaling factors is not guaranteed to reduce the condition
48*> number of A but works well in practice.
49*>
50*> This routine differs from DGEEQU by restricting the scaling factors
51*> to a power of the radix. Barring over- and underflow, scaling by
52*> these factors introduces no additional rounding errors. However, the
53*> scaled entries' magnitudes are no longer approximately 1 but lie
54*> between sqrt(radix) and 1/sqrt(radix).
55*> \endverbatim
56*
57* Arguments:
58* ==========
59*
60*> \param[in] M
61*> \verbatim
62*> M is INTEGER
63*> The number of rows of the matrix A. M >= 0.
64*> \endverbatim
65*>
66*> \param[in] N
67*> \verbatim
68*> N is INTEGER
69*> The number of columns of the matrix A. N >= 0.
70*> \endverbatim
71*>
72*> \param[in] KL
73*> \verbatim
74*> KL is INTEGER
75*> The number of subdiagonals within the band of A. KL >= 0.
76*> \endverbatim
77*>
78*> \param[in] KU
79*> \verbatim
80*> KU is INTEGER
81*> The number of superdiagonals within the band of A. KU >= 0.
82*> \endverbatim
83*>
84*> \param[in] AB
85*> \verbatim
86*> AB is DOUBLE PRECISION array, dimension (LDAB,N)
87*> On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
88*> The j-th column of A is stored in the j-th column of the
89*> array AB as follows:
90*> AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
91*> \endverbatim
92*>
93*> \param[in] LDAB
94*> \verbatim
95*> LDAB is INTEGER
96*> The leading dimension of the array A. LDAB >= max(1,M).
97*> \endverbatim
98*>
99*> \param[out] R
100*> \verbatim
101*> R is DOUBLE PRECISION array, dimension (M)
102*> If INFO = 0 or INFO > M, R contains the row scale factors
103*> for A.
104*> \endverbatim
105*>
106*> \param[out] C
107*> \verbatim
108*> C is DOUBLE PRECISION array, dimension (N)
109*> If INFO = 0, C contains the column scale factors for A.
110*> \endverbatim
111*>
112*> \param[out] ROWCND
113*> \verbatim
114*> ROWCND is DOUBLE PRECISION
115*> If INFO = 0 or INFO > M, ROWCND contains the ratio of the
116*> smallest R(i) to the largest R(i). If ROWCND >= 0.1 and
117*> AMAX is neither too large nor too small, it is not worth
118*> scaling by R.
119*> \endverbatim
120*>
121*> \param[out] COLCND
122*> \verbatim
123*> COLCND is DOUBLE PRECISION
124*> If INFO = 0, COLCND contains the ratio of the smallest
125*> C(i) to the largest C(i). If COLCND >= 0.1, it is not
126*> worth scaling by C.
127*> \endverbatim
128*>
129*> \param[out] AMAX
130*> \verbatim
131*> AMAX is DOUBLE PRECISION
132*> Absolute value of largest matrix element. If AMAX is very
133*> close to overflow or very close to underflow, the matrix
134*> should be scaled.
135*> \endverbatim
136*>
137*> \param[out] INFO
138*> \verbatim
139*> INFO is INTEGER
140*> = 0: successful exit
141*> < 0: if INFO = -i, the i-th argument had an illegal value
142*> > 0: if INFO = i, and i is
143*> <= M: the i-th row of A is exactly zero
144*> > M: the (i-M)-th column of A is exactly zero
145*> \endverbatim
146*
147* Authors:
148* ========
149*
150*> \author Univ. of Tennessee
151*> \author Univ. of California Berkeley
152*> \author Univ. of Colorado Denver
153*> \author NAG Ltd.
154*
155*> \ingroup gbequb
156*
157* =====================================================================
158 SUBROUTINE dgbequb( M, N, KL, KU, AB, LDAB, R, C, ROWCND, 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 AB( LDAB, * ), C( * ), R( * )
171* ..
172*
173* =====================================================================
174*
175* .. Parameters ..
176 DOUBLE PRECISION ONE, ZERO
177 parameter( one = 1.0d+0, zero = 0.0d+0 )
178* ..
179* .. Local Scalars ..
180 INTEGER I, J, KD
181 DOUBLE PRECISION BIGNUM, RCMAX, RCMIN, SMLNUM, RADIX, LOGRDX
182* ..
183* .. External Functions ..
184 DOUBLE PRECISION DLAMCH
185 EXTERNAL dlamch
186* ..
187* .. External Subroutines ..
188 EXTERNAL xerbla
189* ..
190* .. Intrinsic Functions ..
191 INTRINSIC abs, max, min, log
192* ..
193* .. Executable Statements ..
194*
195* Test the input parameters.
196*
197 info = 0
198 IF( m.LT.0 ) THEN
199 info = -1
200 ELSE IF( n.LT.0 ) THEN
201 info = -2
202 ELSE IF( kl.LT.0 ) THEN
203 info = -3
204 ELSE IF( ku.LT.0 ) THEN
205 info = -4
206 ELSE IF( ldab.LT.kl+ku+1 ) THEN
207 info = -6
208 END IF
209 IF( info.NE.0 ) THEN
210 CALL xerbla( 'DGBEQUB', -info )
211 RETURN
212 END IF
213*
214* Quick return if possible.
215*
216 IF( m.EQ.0 .OR. n.EQ.0 ) THEN
217 rowcnd = one
218 colcnd = one
219 amax = zero
220 RETURN
221 END IF
222*
223* Get machine constants. Assume SMLNUM is a power of the radix.
224*
225 smlnum = dlamch( 'S' )
226 bignum = one / smlnum
227 radix = dlamch( 'B' )
228 logrdx = log(radix)
229*
230* Compute row scale factors.
231*
232 DO 10 i = 1, m
233 r( i ) = zero
234 10 CONTINUE
235*
236* Find the maximum element in each row.
237*
238 kd = ku + 1
239 DO 30 j = 1, n
240 DO 20 i = max( j-ku, 1 ), min( j+kl, m )
241 r( i ) = max( r( i ), abs( ab( kd+i-j, j ) ) )
242 20 CONTINUE
243 30 CONTINUE
244 DO i = 1, m
245 IF( r( i ).GT.zero ) THEN
246 r( i ) = radix**int( log( r( i ) ) / logrdx )
247 END IF
248 END DO
249*
250* Find the maximum and minimum scale factors.
251*
252 rcmin = bignum
253 rcmax = zero
254 DO 40 i = 1, m
255 rcmax = max( rcmax, r( i ) )
256 rcmin = min( rcmin, r( i ) )
257 40 CONTINUE
258 amax = rcmax
259*
260 IF( rcmin.EQ.zero ) THEN
261*
262* Find the first zero scale factor and return an error code.
263*
264 DO 50 i = 1, m
265 IF( r( i ).EQ.zero ) THEN
266 info = i
267 RETURN
268 END IF
269 50 CONTINUE
270 ELSE
271*
272* Invert the scale factors.
273*
274 DO 60 i = 1, m
275 r( i ) = one / min( max( r( i ), smlnum ), bignum )
276 60 CONTINUE
277*
278* Compute ROWCND = min(R(I)) / max(R(I)).
279*
280 rowcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
281 END IF
282*
283* Compute column scale factors.
284*
285 DO 70 j = 1, n
286 c( j ) = zero
287 70 CONTINUE
288*
289* Find the maximum element in each column,
290* assuming the row scaling computed above.
291*
292 DO 90 j = 1, n
293 DO 80 i = max( j-ku, 1 ), min( j+kl, m )
294 c( j ) = max( c( j ), abs( ab( kd+i-j, j ) )*r( i ) )
295 80 CONTINUE
296 IF( c( j ).GT.zero ) THEN
297 c( j ) = radix**int( log( c( j ) ) / logrdx )
298 END IF
299 90 CONTINUE
300*
301* Find the maximum and minimum scale factors.
302*
303 rcmin = bignum
304 rcmax = zero
305 DO 100 j = 1, n
306 rcmin = min( rcmin, c( j ) )
307 rcmax = max( rcmax, c( j ) )
308 100 CONTINUE
309*
310 IF( rcmin.EQ.zero ) THEN
311*
312* Find the first zero scale factor and return an error code.
313*
314 DO 110 j = 1, n
315 IF( c( j ).EQ.zero ) THEN
316 info = m + j
317 RETURN
318 END IF
319 110 CONTINUE
320 ELSE
321*
322* Invert the scale factors.
323*
324 DO 120 j = 1, n
325 c( j ) = one / min( max( c( j ), smlnum ), bignum )
326 120 CONTINUE
327*
328* Compute COLCND = min(C(J)) / max(C(J)).
329*
330 colcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
331 END IF
332*
333 RETURN
334*
335* End of DGBEQUB
336*
337 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dgbequb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)
DGBEQUB
Definition dgbequb.f:160