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