1 *> \brief \b DLAQGB scales a general band matrix, using row and column scaling factors computed by sgbequ.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DLAQGB + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaqgb.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaqgb.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaqgb.f">
21 * SUBROUTINE DLAQGB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
24 * .. Scalar Arguments ..
26 * INTEGER KL, KU, LDAB, M, N
27 * DOUBLE PRECISION AMAX, COLCND, ROWCND
29 * .. Array Arguments ..
30 * DOUBLE PRECISION AB( LDAB, * ), C( * ), R( * )
39 *> DLAQGB 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.
50 *> The number of rows of the matrix A. M >= 0.
56 *> The number of columns of the matrix A. N >= 0.
62 *> The number of subdiagonals within the band of A. KL >= 0.
68 *> The number of superdiagonals within the band of A. KU >= 0.
73 *> AB is DOUBLE PRECISION 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)
79 *> On exit, the equilibrated matrix, in the same storage format
80 *> as A. See EQUED for the form of the equilibrated matrix.
86 *> The leading dimension of the array AB. LDA >= KL+KU+1.
91 *> R is DOUBLE PRECISION array, dimension (M)
92 *> The row scale factors for A.
97 *> C is DOUBLE PRECISION array, dimension (N)
98 *> The column scale factors for A.
103 *> ROWCND is DOUBLE PRECISION
104 *> Ratio of the smallest R(i) to the largest R(i).
109 *> COLCND is DOUBLE PRECISION
110 *> Ratio of the smallest C(i) to the largest C(i).
115 *> AMAX is DOUBLE PRECISION
116 *> Absolute value of largest matrix entry.
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
126 *> = 'C': Column equilibration, i.e., A has been postmultiplied
128 *> = 'B': Both row and column equilibration, i.e., A has been
129 *> replaced by diag(R) * A * diag(C).
132 *> \par Internal Parameters:
133 * =========================
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.
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.
149 *> \author Univ. of Tennessee
150 *> \author Univ. of California Berkeley
151 *> \author Univ. of Colorado Denver
154 *> \date September 2012
156 *> \ingroup doubleGBauxiliary
158 * =====================================================================
159 SUBROUTINE DLAQGB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
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..--
167 * .. Scalar Arguments ..
169 INTEGER KL, KU, LDAB, M, N
170 DOUBLE PRECISION AMAX, COLCND, ROWCND
172 * .. Array Arguments ..
173 DOUBLE PRECISION AB( LDAB, * ), C( * ), R( * )
176 * =====================================================================
179 DOUBLE PRECISION ONE, THRESH
180 PARAMETER ( ONE = 1.0D+0, THRESH = 0.1D+0 )
182 * .. Local Scalars ..
184 DOUBLE PRECISION CJ, LARGE, SMALL
186 * .. External Functions ..
187 DOUBLE PRECISION DLAMCH
190 * .. Intrinsic Functions ..
193 * .. Executable Statements ..
195 * Quick return if possible
197 IF( M.LE.0 .OR. N.LE.0 ) THEN
202 * Initialize LARGE and SMALL.
204 SMALL = DLAMCH( 'Safe minimum' ) / DLAMCH( 'Precision' )
207 IF( ROWCND.GE.THRESH .AND. AMAX.GE.SMALL .AND. AMAX.LE.LARGE )
212 IF( COLCND.GE.THRESH ) THEN
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 )
229 ELSE IF( COLCND.GE.THRESH ) THEN
231 * Row scaling, no column scaling
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 )
241 * Row and column scaling
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 )