LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
csrscl.f
Go to the documentation of this file.
1*> \brief \b CSRSCL multiplies a vector by the reciprocal of a real scalar.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CSRSCL + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/csrscl.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/csrscl.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/csrscl.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CSRSCL( N, SA, SX, INCX )
20*
21* .. Scalar Arguments ..
22* INTEGER INCX, N
23* REAL SA
24* ..
25* .. Array Arguments ..
26* COMPLEX SX( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CSRSCL multiplies an n-element complex vector x by the real scalar
36*> 1/a. This is done without overflow or underflow as long as
37*> the final result x/a does not overflow or underflow.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] N
44*> \verbatim
45*> N is INTEGER
46*> The number of components of the vector x.
47*> \endverbatim
48*>
49*> \param[in] SA
50*> \verbatim
51*> SA is REAL
52*> The scalar a which is used to divide each component of x.
53*> SA must be >= 0, or the subroutine will divide by zero.
54*> \endverbatim
55*>
56*> \param[in,out] SX
57*> \verbatim
58*> SX is COMPLEX array, dimension
59*> (1+(N-1)*abs(INCX))
60*> The n-element vector x.
61*> \endverbatim
62*>
63*> \param[in] INCX
64*> \verbatim
65*> INCX is INTEGER
66*> The increment between successive values of the vector SX.
67*> > 0: SX(1) = X(1) and SX(1+(i-1)*INCX) = x(i), 1< i<= n
68*> \endverbatim
69*
70* Authors:
71* ========
72*
73*> \author Univ. of Tennessee
74*> \author Univ. of California Berkeley
75*> \author Univ. of Colorado Denver
76*> \author NAG Ltd.
77*
78*> \ingroup rscl
79*
80* =====================================================================
81 SUBROUTINE csrscl( N, SA, SX, INCX )
82*
83* -- LAPACK auxiliary routine --
84* -- LAPACK is a software package provided by Univ. of Tennessee, --
85* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
86*
87* .. Scalar Arguments ..
88 INTEGER INCX, N
89 REAL SA
90* ..
91* .. Array Arguments ..
92 COMPLEX SX( * )
93* ..
94*
95* =====================================================================
96*
97* .. Parameters ..
98 REAL ZERO, ONE
99 parameter( zero = 0.0e+0, one = 1.0e+0 )
100* ..
101* .. Local Scalars ..
102 LOGICAL DONE
103 REAL BIGNUM, CDEN, CDEN1, CNUM, CNUM1, MUL, SMLNUM
104* ..
105* .. External Functions ..
106 REAL SLAMCH
107 EXTERNAL slamch
108* ..
109* .. External Subroutines ..
110 EXTERNAL csscal
111* ..
112* .. Intrinsic Functions ..
113 INTRINSIC abs
114* ..
115* .. Executable Statements ..
116*
117* Quick return if possible
118*
119 IF( n.LE.0 )
120 $ RETURN
121*
122* Get machine parameters
123*
124 smlnum = slamch( 'S' )
125 bignum = one / smlnum
126*
127* Initialize the denominator to SA and the numerator to 1.
128*
129 cden = sa
130 cnum = one
131*
132 10 CONTINUE
133 cden1 = cden*smlnum
134 cnum1 = cnum / bignum
135 IF( abs( cden1 ).GT.abs( cnum ) .AND. cnum.NE.zero ) THEN
136*
137* Pre-multiply X by SMLNUM if CDEN is large compared to CNUM.
138*
139 mul = smlnum
140 done = .false.
141 cden = cden1
142 ELSE IF( abs( cnum1 ).GT.abs( cden ) ) THEN
143*
144* Pre-multiply X by BIGNUM if CDEN is small compared to CNUM.
145*
146 mul = bignum
147 done = .false.
148 cnum = cnum1
149 ELSE
150*
151* Multiply X by CNUM / CDEN and return.
152*
153 mul = cnum / cden
154 done = .true.
155 END IF
156*
157* Scale the vector X by MUL
158*
159 CALL csscal( n, mul, sx, incx )
160*
161 IF( .NOT.done )
162 $ GO TO 10
163*
164 RETURN
165*
166* End of CSRSCL
167*
168 END
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.
Definition csrscl.f:82
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78