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