1 *> \brief \b CLAQGB 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 CLAQGB + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/claqgb.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/claqgb.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/claqgb.f">
21 * SUBROUTINE CLAQGB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
24 * .. Scalar Arguments ..
26 * INTEGER KL, KU, LDAB, M, N
27 * REAL AMAX, COLCND, ROWCND
29 * .. Array Arguments ..
31 * COMPLEX AB( LDAB, * )
40 *> CLAQGB equilibrates a general M by N band matrix A with KL
41 *> subdiagonals and KU superdiagonals using the row and scaling factors
42 *> in the vectors R and C.
51 *> The number of rows of the matrix A. M >= 0.
57 *> The number of columns of the matrix A. N >= 0.
63 *> The number of subdiagonals within the band of A. KL >= 0.
69 *> The number of superdiagonals within the band of A. KU >= 0.
74 *> AB is COMPLEX array, dimension (LDAB,N)
75 *> On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
76 *> The j-th column of A is stored in the j-th column of the
77 *> array AB as follows:
78 *> AB(ku+1+i-j,j) = A(i,j) for max(1,j-ku)<=i<=min(m,j+kl)
80 *> On exit, the equilibrated matrix, in the same storage format
81 *> as A. See EQUED for the form of the equilibrated matrix.
87 *> The leading dimension of the array AB. LDA >= KL+KU+1.
92 *> R is REAL array, dimension (M)
93 *> The row scale factors for A.
98 *> C is REAL array, dimension (N)
99 *> The column scale factors for A.
105 *> Ratio of the smallest R(i) to the largest R(i).
111 *> Ratio of the smallest C(i) to the largest C(i).
117 *> Absolute value of largest matrix entry.
122 *> EQUED is CHARACTER*1
123 *> Specifies the form of equilibration that was done.
124 *> = 'N': No equilibration
125 *> = 'R': Row equilibration, i.e., A has been premultiplied by
127 *> = 'C': Column equilibration, i.e., A has been postmultiplied
129 *> = 'B': Both row and column equilibration, i.e., A has been
130 *> replaced by diag(R) * A * diag(C).
133 *> \par Internal Parameters:
134 * =========================
137 *> THRESH is a threshold value used to decide if row or column scaling
138 *> should be done based on the ratio of the row or column scaling
139 *> factors. If ROWCND < THRESH, row scaling is done, and if
140 *> COLCND < THRESH, column scaling is done.
142 *> LARGE and SMALL are threshold values used to decide if row scaling
143 *> should be done based on the absolute size of the largest matrix
144 *> element. If AMAX > LARGE or AMAX < SMALL, row scaling is done.
150 *> \author Univ. of Tennessee
151 *> \author Univ. of California Berkeley
152 *> \author Univ. of Colorado Denver
155 *> \date September 2012
157 *> \ingroup complexGBauxiliary
159 * =====================================================================
160 SUBROUTINE CLAQGB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
163 * -- LAPACK auxiliary routine (version 3.4.2) --
164 * -- LAPACK is a software package provided by Univ. of Tennessee, --
165 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168 * .. Scalar Arguments ..
170 INTEGER KL, KU, LDAB, M, N
171 REAL AMAX, COLCND, ROWCND
173 * .. Array Arguments ..
175 COMPLEX AB( LDAB, * )
178 * =====================================================================
182 PARAMETER ( ONE = 1.0E+0, THRESH = 0.1E+0 )
184 * .. Local Scalars ..
186 REAL CJ, LARGE, SMALL
188 * .. External Functions ..
192 * .. Intrinsic Functions ..
195 * .. Executable Statements ..
197 * Quick return if possible
199 IF( M.LE.0 .OR. N.LE.0 ) THEN
204 * Initialize LARGE and SMALL.
206 SMALL = SLAMCH( 'Safe minimum' ) / SLAMCH( 'Precision' )
209 IF( ROWCND.GE.THRESH .AND. AMAX.GE.SMALL .AND. AMAX.LE.LARGE )
214 IF( COLCND.GE.THRESH ) THEN
225 DO 10 I = MAX( 1, J-KU ), MIN( M, J+KL )
226 AB( KU+1+I-J, J ) = CJ*AB( KU+1+I-J, J )
231 ELSE IF( COLCND.GE.THRESH ) THEN
233 * Row scaling, no column scaling
236 DO 30 I = MAX( 1, J-KU ), MIN( M, J+KL )
237 AB( KU+1+I-J, J ) = R( I )*AB( KU+1+I-J, J )
243 * Row and column scaling
247 DO 50 I = MAX( 1, J-KU ), MIN( M, J+KL )
248 AB( KU+1+I-J, J ) = CJ*R( I )*AB( KU+1+I-J, J )