1 *> \brief \b DLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DLASCL + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlascl.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlascl.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlascl.f">
21 * SUBROUTINE DLASCL( TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, KL, KU, LDA, M, N
26 * DOUBLE PRECISION CFROM, CTO
28 * .. Array Arguments ..
29 * DOUBLE PRECISION A( LDA, * )
38 *> DLASCL multiplies the M by N real matrix A by the real scalar
39 *> CTO/CFROM. This is done without over/underflow as long as the final
40 *> result CTO*A(I,J)/CFROM does not over/underflow. TYPE specifies that
41 *> A may be full, upper triangular, lower triangular, upper Hessenberg,
50 *> TYPE is CHARACTER*1
51 *> TYPE indices the storage type of the input matrix.
52 *> = 'G': A is a full matrix.
53 *> = 'L': A is a lower triangular matrix.
54 *> = 'U': A is an upper triangular matrix.
55 *> = 'H': A is an upper Hessenberg matrix.
56 *> = 'B': A is a symmetric band matrix with lower bandwidth KL
57 *> and upper bandwidth KU and with the only the lower
59 *> = 'Q': A is a symmetric band matrix with lower bandwidth KL
60 *> and upper bandwidth KU and with the only the upper
62 *> = 'Z': A is a band matrix with lower bandwidth KL and upper
63 *> bandwidth KU. See DGBTRF for storage details.
69 *> The lower bandwidth of A. Referenced only if TYPE = 'B',
76 *> The upper bandwidth of A. Referenced only if TYPE = 'B',
82 *> CFROM is DOUBLE PRECISION
87 *> CTO is DOUBLE PRECISION
89 *> The matrix A is multiplied by CTO/CFROM. A(I,J) is computed
90 *> without over/underflow if the final result CTO*A(I,J)/CFROM
91 *> can be represented without over/underflow. CFROM must be
98 *> The number of rows of the matrix A. M >= 0.
104 *> The number of columns of the matrix A. N >= 0.
109 *> A is DOUBLE PRECISION array, dimension (LDA,N)
110 *> The matrix to be multiplied by CTO/CFROM. See TYPE for the
117 *> The leading dimension of the array A.
118 *> If TYPE = 'G', 'L', 'U', 'H', LDA >= max(1,M);
119 *> TYPE = 'B', LDA >= KL+1;
120 *> TYPE = 'Q', LDA >= KU+1;
121 *> TYPE = 'Z', LDA >= 2*KL+KU+1.
127 *> 0 - successful exit
128 *> <0 - if INFO = -i, the i-th argument had an illegal value.
134 *> \author Univ. of Tennessee
135 *> \author Univ. of California Berkeley
136 *> \author Univ. of Colorado Denver
141 *> \ingroup OTHERauxiliary
143 * =====================================================================
144 SUBROUTINE DLASCL( TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO )
146 * -- LAPACK auxiliary routine (version 3.6.1) --
147 * -- LAPACK is a software package provided by Univ. of Tennessee, --
148 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
151 * .. Scalar Arguments ..
153 INTEGER INFO, KL, KU, LDA, M, N
154 DOUBLE PRECISION CFROM, CTO
156 * .. Array Arguments ..
157 DOUBLE PRECISION A( LDA, * )
160 * =====================================================================
163 DOUBLE PRECISION ZERO, ONE
164 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
166 * .. Local Scalars ..
168 INTEGER I, ITYPE, J, K1, K2, K3, K4
169 DOUBLE PRECISION BIGNUM, CFROM1, CFROMC, CTO1, CTOC, MUL, SMLNUM
171 * .. External Functions ..
172 LOGICAL LSAME, DISNAN
173 DOUBLE PRECISION DLAMCH
174 EXTERNAL LSAME, DLAMCH, DISNAN
176 * .. Intrinsic Functions ..
177 INTRINSIC ABS, MAX, MIN
179 * .. External Subroutines ..
182 * .. Executable Statements ..
184 * Test the input arguments
188 IF( LSAME( TYPE, 'G' ) ) THEN
190 ELSE IF( LSAME( TYPE, 'L' ) ) THEN
192 ELSE IF( LSAME( TYPE, 'U' ) ) THEN
194 ELSE IF( LSAME( TYPE, 'H' ) ) THEN
196 ELSE IF( LSAME( TYPE, 'B' ) ) THEN
198 ELSE IF( LSAME( TYPE, 'Q' ) ) THEN
200 ELSE IF( LSAME( TYPE, 'Z' ) ) THEN
206 IF( ITYPE.EQ.-1 ) THEN
208 ELSE IF( CFROM.EQ.ZERO .OR. DISNAN(CFROM) ) THEN
210 ELSE IF( DISNAN(CTO) ) THEN
212 ELSE IF( M.LT.0 ) THEN
214 ELSE IF( N.LT.0 .OR. ( ITYPE.EQ.4 .AND. N.NE.M ) .OR.
215 $ ( ITYPE.EQ.5 .AND. N.NE.M ) ) THEN
217 ELSE IF( ITYPE.LE.3 .AND. LDA.LT.MAX( 1, M ) ) THEN
219 ELSE IF( ITYPE.GE.4 ) THEN
220 IF( KL.LT.0 .OR. KL.GT.MAX( M-1, 0 ) ) THEN
222 ELSE IF( KU.LT.0 .OR. KU.GT.MAX( N-1, 0 ) .OR.
223 $ ( ( ITYPE.EQ.4 .OR. ITYPE.EQ.5 ) .AND. KL.NE.KU ) )
226 ELSE IF( ( ITYPE.EQ.4 .AND. LDA.LT.KL+1 ) .OR.
227 $ ( ITYPE.EQ.5 .AND. LDA.LT.KU+1 ) .OR.
228 $ ( ITYPE.EQ.6 .AND. LDA.LT.2*KL+KU+1 ) ) THEN
234 CALL XERBLA( 'DLASCL', -INFO )
238 * Quick return if possible
240 IF( N.EQ.0 .OR. M.EQ.0 )
243 * Get machine parameters
245 SMLNUM = DLAMCH( 'S' )
246 BIGNUM = ONE / SMLNUM
252 CFROM1 = CFROMC*SMLNUM
253 IF( CFROM1.EQ.CFROMC ) THEN
254 ! CFROMC is an inf. Multiply by a correctly signed zero for
255 ! finite CTOC, or a NaN if CTOC is infinite.
261 IF( CTO1.EQ.CTOC ) THEN
262 ! CTOC is either 0 or an inf. In both cases, CTOC itself
263 ! serves as the correct multiplication factor.
267 ELSE IF( ABS( CFROM1 ).GT.ABS( CTOC ) .AND. CTOC.NE.ZERO ) THEN
271 ELSE IF( ABS( CTO1 ).GT.ABS( CFROMC ) ) THEN
281 IF( ITYPE.EQ.0 ) THEN
287 A( I, J ) = A( I, J )*MUL
291 ELSE IF( ITYPE.EQ.1 ) THEN
293 * Lower triangular matrix
297 A( I, J ) = A( I, J )*MUL
301 ELSE IF( ITYPE.EQ.2 ) THEN
303 * Upper triangular matrix
306 DO 60 I = 1, MIN( J, M )
307 A( I, J ) = A( I, J )*MUL
311 ELSE IF( ITYPE.EQ.3 ) THEN
313 * Upper Hessenberg matrix
316 DO 80 I = 1, MIN( J+1, M )
317 A( I, J ) = A( I, J )*MUL
321 ELSE IF( ITYPE.EQ.4 ) THEN
323 * Lower half of a symmetric band matrix
328 DO 100 I = 1, MIN( K3, K4-J )
329 A( I, J ) = A( I, J )*MUL
333 ELSE IF( ITYPE.EQ.5 ) THEN
335 * Upper half of a symmetric band matrix
340 DO 120 I = MAX( K1-J, 1 ), K3
341 A( I, J ) = A( I, J )*MUL
345 ELSE IF( ITYPE.EQ.6 ) THEN
354 DO 140 I = MAX( K1-J, K2 ), MIN( K3, K4-J )
355 A( I, J ) = A( I, J )*MUL