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