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