LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dlascl.f
Go to the documentation of this file.
1 *> \brief \b DLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DLASCL + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlascl.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlascl.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlascl.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DLASCL( TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER TYPE
25 * INTEGER INFO, KL, KU, LDA, M, N
26 * DOUBLE PRECISION CFROM, CTO
27 * ..
28 * .. Array Arguments ..
29 * DOUBLE PRECISION A( LDA, * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
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,
42 *> or banded.
43 *> \endverbatim
44 *
45 * Arguments:
46 * ==========
47 *
48 *> \param[in] TYPE
49 *> \verbatim
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
58 *> half stored.
59 *> = 'Q': A is a symmetric band matrix with lower bandwidth KL
60 *> and upper bandwidth KU and with the only the upper
61 *> half stored.
62 *> = 'Z': A is a band matrix with lower bandwidth KL and upper
63 *> bandwidth KU. See DGBTRF for storage details.
64 *> \endverbatim
65 *>
66 *> \param[in] KL
67 *> \verbatim
68 *> KL is INTEGER
69 *> The lower bandwidth of A. Referenced only if TYPE = 'B',
70 *> 'Q' or 'Z'.
71 *> \endverbatim
72 *>
73 *> \param[in] KU
74 *> \verbatim
75 *> KU is INTEGER
76 *> The upper bandwidth of A. Referenced only if TYPE = 'B',
77 *> 'Q' or 'Z'.
78 *> \endverbatim
79 *>
80 *> \param[in] CFROM
81 *> \verbatim
82 *> CFROM is DOUBLE PRECISION
83 *> \endverbatim
84 *>
85 *> \param[in] CTO
86 *> \verbatim
87 *> CTO is DOUBLE PRECISION
88 *>
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
92 *> nonzero.
93 *> \endverbatim
94 *>
95 *> \param[in] M
96 *> \verbatim
97 *> M is INTEGER
98 *> The number of rows of the matrix A. M >= 0.
99 *> \endverbatim
100 *>
101 *> \param[in] N
102 *> \verbatim
103 *> N is INTEGER
104 *> The number of columns of the matrix A. N >= 0.
105 *> \endverbatim
106 *>
107 *> \param[in,out] A
108 *> \verbatim
109 *> A is DOUBLE PRECISION array, dimension (LDA,N)
110 *> The matrix to be multiplied by CTO/CFROM. See TYPE for the
111 *> storage type.
112 *> \endverbatim
113 *>
114 *> \param[in] LDA
115 *> \verbatim
116 *> LDA is INTEGER
117 *> The leading dimension of the array A. LDA >= max(1,M).
118 *> \endverbatim
119 *>
120 *> \param[out] INFO
121 *> \verbatim
122 *> INFO is INTEGER
123 *> 0 - successful exit
124 *> <0 - if INFO = -i, the i-th argument had an illegal value.
125 *> \endverbatim
126 *
127 * Authors:
128 * ========
129 *
130 *> \author Univ. of Tennessee
131 *> \author Univ. of California Berkeley
132 *> \author Univ. of Colorado Denver
133 *> \author NAG Ltd.
134 *
135 *> \date September 2012
136 *
137 *> \ingroup auxOTHERauxiliary
138 *
139 * =====================================================================
140  SUBROUTINE dlascl( TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO )
141 *
142 * -- LAPACK auxiliary routine (version 3.4.2) --
143 * -- LAPACK is a software package provided by Univ. of Tennessee, --
144 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
145 * September 2012
146 *
147 * .. Scalar Arguments ..
148  CHARACTER type
149  INTEGER info, kl, ku, lda, m, n
150  DOUBLE PRECISION cfrom, cto
151 * ..
152 * .. Array Arguments ..
153  DOUBLE PRECISION a( lda, * )
154 * ..
155 *
156 * =====================================================================
157 *
158 * .. Parameters ..
159  DOUBLE PRECISION zero, one
160  parameter( zero = 0.0d0, one = 1.0d0 )
161 * ..
162 * .. Local Scalars ..
163  LOGICAL done
164  INTEGER i, itype, j, k1, k2, k3, k4
165  DOUBLE PRECISION bignum, cfrom1, cfromc, cto1, ctoc, mul, smlnum
166 * ..
167 * .. External Functions ..
168  LOGICAL lsame, disnan
169  DOUBLE PRECISION dlamch
170  EXTERNAL lsame, dlamch, disnan
171 * ..
172 * .. Intrinsic Functions ..
173  INTRINSIC abs, max, min
174 * ..
175 * .. External Subroutines ..
176  EXTERNAL xerbla
177 * ..
178 * .. Executable Statements ..
179 *
180 * Test the input arguments
181 *
182  info = 0
183 *
184  IF( lsame( type, 'G' ) ) THEN
185  itype = 0
186  ELSE IF( lsame( type, 'L' ) ) THEN
187  itype = 1
188  ELSE IF( lsame( type, 'U' ) ) THEN
189  itype = 2
190  ELSE IF( lsame( type, 'H' ) ) THEN
191  itype = 3
192  ELSE IF( lsame( type, 'B' ) ) THEN
193  itype = 4
194  ELSE IF( lsame( type, 'Q' ) ) THEN
195  itype = 5
196  ELSE IF( lsame( type, 'Z' ) ) THEN
197  itype = 6
198  ELSE
199  itype = -1
200  END IF
201 *
202  IF( itype.EQ.-1 ) THEN
203  info = -1
204  ELSE IF( cfrom.EQ.zero .OR. disnan(cfrom) ) THEN
205  info = -4
206  ELSE IF( disnan(cto) ) THEN
207  info = -5
208  ELSE IF( m.LT.0 ) THEN
209  info = -6
210  ELSE IF( n.LT.0 .OR. ( itype.EQ.4 .AND. n.NE.m ) .OR.
211  $ ( itype.EQ.5 .AND. n.NE.m ) ) THEN
212  info = -7
213  ELSE IF( itype.LE.3 .AND. lda.LT.max( 1, m ) ) THEN
214  info = -9
215  ELSE IF( itype.GE.4 ) THEN
216  IF( kl.LT.0 .OR. kl.GT.max( m-1, 0 ) ) THEN
217  info = -2
218  ELSE IF( ku.LT.0 .OR. ku.GT.max( n-1, 0 ) .OR.
219  $ ( ( itype.EQ.4 .OR. itype.EQ.5 ) .AND. kl.NE.ku ) )
220  $ THEN
221  info = -3
222  ELSE IF( ( itype.EQ.4 .AND. lda.LT.kl+1 ) .OR.
223  $ ( itype.EQ.5 .AND. lda.LT.ku+1 ) .OR.
224  $ ( itype.EQ.6 .AND. lda.LT.2*kl+ku+1 ) ) THEN
225  info = -9
226  END IF
227  END IF
228 *
229  IF( info.NE.0 ) THEN
230  CALL xerbla( 'DLASCL', -info )
231  return
232  END IF
233 *
234 * Quick return if possible
235 *
236  IF( n.EQ.0 .OR. m.EQ.0 )
237  $ return
238 *
239 * Get machine parameters
240 *
241  smlnum = dlamch( 'S' )
242  bignum = one / smlnum
243 *
244  cfromc = cfrom
245  ctoc = cto
246 *
247  10 continue
248  cfrom1 = cfromc*smlnum
249  IF( cfrom1.EQ.cfromc ) THEN
250 ! CFROMC is an inf. Multiply by a correctly signed zero for
251 ! finite CTOC, or a NaN if CTOC is infinite.
252  mul = ctoc / cfromc
253  done = .true.
254  cto1 = ctoc
255  ELSE
256  cto1 = ctoc / bignum
257  IF( cto1.EQ.ctoc ) THEN
258 ! CTOC is either 0 or an inf. In both cases, CTOC itself
259 ! serves as the correct multiplication factor.
260  mul = ctoc
261  done = .true.
262  cfromc = one
263  ELSE IF( abs( cfrom1 ).GT.abs( ctoc ) .AND. ctoc.NE.zero ) THEN
264  mul = smlnum
265  done = .false.
266  cfromc = cfrom1
267  ELSE IF( abs( cto1 ).GT.abs( cfromc ) ) THEN
268  mul = bignum
269  done = .false.
270  ctoc = cto1
271  ELSE
272  mul = ctoc / cfromc
273  done = .true.
274  END IF
275  END IF
276 *
277  IF( itype.EQ.0 ) THEN
278 *
279 * Full matrix
280 *
281  DO 30 j = 1, n
282  DO 20 i = 1, m
283  a( i, j ) = a( i, j )*mul
284  20 continue
285  30 continue
286 *
287  ELSE IF( itype.EQ.1 ) THEN
288 *
289 * Lower triangular matrix
290 *
291  DO 50 j = 1, n
292  DO 40 i = j, m
293  a( i, j ) = a( i, j )*mul
294  40 continue
295  50 continue
296 *
297  ELSE IF( itype.EQ.2 ) THEN
298 *
299 * Upper triangular matrix
300 *
301  DO 70 j = 1, n
302  DO 60 i = 1, min( j, m )
303  a( i, j ) = a( i, j )*mul
304  60 continue
305  70 continue
306 *
307  ELSE IF( itype.EQ.3 ) THEN
308 *
309 * Upper Hessenberg matrix
310 *
311  DO 90 j = 1, n
312  DO 80 i = 1, min( j+1, m )
313  a( i, j ) = a( i, j )*mul
314  80 continue
315  90 continue
316 *
317  ELSE IF( itype.EQ.4 ) THEN
318 *
319 * Lower half of a symmetric band matrix
320 *
321  k3 = kl + 1
322  k4 = n + 1
323  DO 110 j = 1, n
324  DO 100 i = 1, min( k3, k4-j )
325  a( i, j ) = a( i, j )*mul
326  100 continue
327  110 continue
328 *
329  ELSE IF( itype.EQ.5 ) THEN
330 *
331 * Upper half of a symmetric band matrix
332 *
333  k1 = ku + 2
334  k3 = ku + 1
335  DO 130 j = 1, n
336  DO 120 i = max( k1-j, 1 ), k3
337  a( i, j ) = a( i, j )*mul
338  120 continue
339  130 continue
340 *
341  ELSE IF( itype.EQ.6 ) THEN
342 *
343 * Band matrix
344 *
345  k1 = kl + ku + 2
346  k2 = kl + 1
347  k3 = 2*kl + ku + 1
348  k4 = kl + ku + 1 + m
349  DO 150 j = 1, n
350  DO 140 i = max( k1-j, k2 ), min( k3, k4-j )
351  a( i, j ) = a( i, j )*mul
352  140 continue
353  150 continue
354 *
355  END IF
356 *
357  IF( .NOT.done )
358  $ go to 10
359 *
360  return
361 *
362 * End of DLASCL
363 *
364  END