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