LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlaqgb.f
Go to the documentation of this file.
1*> \brief \b DLAQGB scales a general band matrix, using row and column scaling factors computed by sgbequ.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLAQGB + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaqgb.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaqgb.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaqgb.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLAQGB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
20* AMAX, EQUED )
21*
22* .. Scalar Arguments ..
23* CHARACTER EQUED
24* INTEGER KL, KU, LDAB, M, N
25* DOUBLE PRECISION AMAX, COLCND, ROWCND
26* ..
27* .. Array Arguments ..
28* DOUBLE PRECISION AB( LDAB, * ), C( * ), R( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> DLAQGB equilibrates a general M by N band matrix A with KL
38*> subdiagonals and KU superdiagonals using the row and scaling factors
39*> in the vectors R and C.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] M
46*> \verbatim
47*> M is INTEGER
48*> The number of rows of the matrix A. M >= 0.
49*> \endverbatim
50*>
51*> \param[in] N
52*> \verbatim
53*> N is INTEGER
54*> The number of columns of the matrix A. N >= 0.
55*> \endverbatim
56*>
57*> \param[in] KL
58*> \verbatim
59*> KL is INTEGER
60*> The number of subdiagonals within the band of A. KL >= 0.
61*> \endverbatim
62*>
63*> \param[in] KU
64*> \verbatim
65*> KU is INTEGER
66*> The number of superdiagonals within the band of A. KU >= 0.
67*> \endverbatim
68*>
69*> \param[in,out] AB
70*> \verbatim
71*> AB is DOUBLE PRECISION array, dimension (LDAB,N)
72*> On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
73*> The j-th column of A is stored in the j-th column of the
74*> array AB as follows:
75*> AB(ku+1+i-j,j) = A(i,j) for max(1,j-ku)<=i<=min(m,j+kl)
76*>
77*> On exit, the equilibrated matrix, in the same storage format
78*> as A. See EQUED for the form of the equilibrated matrix.
79*> \endverbatim
80*>
81*> \param[in] LDAB
82*> \verbatim
83*> LDAB is INTEGER
84*> The leading dimension of the array AB. LDA >= KL+KU+1.
85*> \endverbatim
86*>
87*> \param[in] R
88*> \verbatim
89*> R is DOUBLE PRECISION array, dimension (M)
90*> The row scale factors for A.
91*> \endverbatim
92*>
93*> \param[in] C
94*> \verbatim
95*> C is DOUBLE PRECISION array, dimension (N)
96*> The column scale factors for A.
97*> \endverbatim
98*>
99*> \param[in] ROWCND
100*> \verbatim
101*> ROWCND is DOUBLE PRECISION
102*> Ratio of the smallest R(i) to the largest R(i).
103*> \endverbatim
104*>
105*> \param[in] COLCND
106*> \verbatim
107*> COLCND is DOUBLE PRECISION
108*> Ratio of the smallest C(i) to the largest C(i).
109*> \endverbatim
110*>
111*> \param[in] AMAX
112*> \verbatim
113*> AMAX is DOUBLE PRECISION
114*> Absolute value of largest matrix entry.
115*> \endverbatim
116*>
117*> \param[out] EQUED
118*> \verbatim
119*> EQUED is CHARACTER*1
120*> Specifies the form of equilibration that was done.
121*> = 'N': No equilibration
122*> = 'R': Row equilibration, i.e., A has been premultiplied by
123*> diag(R).
124*> = 'C': Column equilibration, i.e., A has been postmultiplied
125*> by diag(C).
126*> = 'B': Both row and column equilibration, i.e., A has been
127*> replaced by diag(R) * A * diag(C).
128*> \endverbatim
129*
130*> \par Internal Parameters:
131* =========================
132*>
133*> \verbatim
134*> THRESH is a threshold value used to decide if row or column scaling
135*> should be done based on the ratio of the row or column scaling
136*> factors. If ROWCND < THRESH, row scaling is done, and if
137*> COLCND < THRESH, column scaling is done.
138*>
139*> LARGE and SMALL are threshold values used to decide if row scaling
140*> should be done based on the absolute size of the largest matrix
141*> element. If AMAX > LARGE or AMAX < SMALL, row scaling is done.
142*> \endverbatim
143*
144* Authors:
145* ========
146*
147*> \author Univ. of Tennessee
148*> \author Univ. of California Berkeley
149*> \author Univ. of Colorado Denver
150*> \author NAG Ltd.
151*
152*> \ingroup laqgb
153*
154* =====================================================================
155 SUBROUTINE dlaqgb( M, N, KL, KU, AB, LDAB, R, C, ROWCND,
156 $ COLCND,
157 $ AMAX, EQUED )
158*
159* -- LAPACK auxiliary routine --
160* -- LAPACK is a software package provided by Univ. of Tennessee, --
161* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162*
163* .. Scalar Arguments ..
164 CHARACTER EQUED
165 INTEGER KL, KU, LDAB, M, N
166 DOUBLE PRECISION AMAX, COLCND, ROWCND
167* ..
168* .. Array Arguments ..
169 DOUBLE PRECISION AB( LDAB, * ), C( * ), R( * )
170* ..
171*
172* =====================================================================
173*
174* .. Parameters ..
175 DOUBLE PRECISION ONE, THRESH
176 PARAMETER ( ONE = 1.0d+0, thresh = 0.1d+0 )
177* ..
178* .. Local Scalars ..
179 INTEGER I, J
180 DOUBLE PRECISION CJ, LARGE, SMALL
181* ..
182* .. External Functions ..
183 DOUBLE PRECISION DLAMCH
184 EXTERNAL DLAMCH
185* ..
186* .. Intrinsic Functions ..
187 INTRINSIC max, min
188* ..
189* .. Executable Statements ..
190*
191* Quick return if possible
192*
193 IF( m.LE.0 .OR. n.LE.0 ) THEN
194 equed = 'N'
195 RETURN
196 END IF
197*
198* Initialize LARGE and SMALL.
199*
200 small = dlamch( 'Safe minimum' ) / dlamch( 'Precision' )
201 large = one / small
202*
203 IF( rowcnd.GE.thresh .AND. amax.GE.small .AND. amax.LE.large )
204 $ THEN
205*
206* No row scaling
207*
208 IF( colcnd.GE.thresh ) THEN
209*
210* No column scaling
211*
212 equed = 'N'
213 ELSE
214*
215* Column scaling
216*
217 DO 20 j = 1, n
218 cj = c( j )
219 DO 10 i = max( 1, j-ku ), min( m, j+kl )
220 ab( ku+1+i-j, j ) = cj*ab( ku+1+i-j, j )
221 10 CONTINUE
222 20 CONTINUE
223 equed = 'C'
224 END IF
225 ELSE IF( colcnd.GE.thresh ) THEN
226*
227* Row scaling, no column scaling
228*
229 DO 40 j = 1, n
230 DO 30 i = max( 1, j-ku ), min( m, j+kl )
231 ab( ku+1+i-j, j ) = r( i )*ab( ku+1+i-j, j )
232 30 CONTINUE
233 40 CONTINUE
234 equed = 'R'
235 ELSE
236*
237* Row and column scaling
238*
239 DO 60 j = 1, n
240 cj = c( j )
241 DO 50 i = max( 1, j-ku ), min( m, j+kl )
242 ab( ku+1+i-j, j ) = cj*r( i )*ab( ku+1+i-j, j )
243 50 CONTINUE
244 60 CONTINUE
245 equed = 'B'
246 END IF
247*
248 RETURN
249*
250* End of DLAQGB
251*
252 END
subroutine dlaqgb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, equed)
DLAQGB scales a general band matrix, using row and column scaling factors computed by sgbequ.
Definition dlaqgb.f:158