LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zrot.f
Go to the documentation of this file.
1*> \brief \b ZROT applies a plane rotation with real cosine and complex sine to a pair of complex vectors.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZROT + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zrot.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zrot.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zrot.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE ZROT( N, CX, INCX, CY, INCY, C, S )
22*
23* .. Scalar Arguments ..
24* INTEGER INCX, INCY, N
25* DOUBLE PRECISION C
26* COMPLEX*16 S
27* ..
28* .. Array Arguments ..
29* COMPLEX*16 CX( * ), CY( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> ZROT applies a plane rotation, where the cos (C) is real and the
39*> sin (S) is complex, and the vectors CX and CY are complex.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] N
46*> \verbatim
47*> N is INTEGER
48*> The number of elements in the vectors CX and CY.
49*> \endverbatim
50*>
51*> \param[in,out] CX
52*> \verbatim
53*> CX is COMPLEX*16 array, dimension (N)
54*> On input, the vector X.
55*> On output, CX is overwritten with C*X + S*Y.
56*> \endverbatim
57*>
58*> \param[in] INCX
59*> \verbatim
60*> INCX is INTEGER
61*> The increment between successive values of CX. INCX <> 0.
62*> \endverbatim
63*>
64*> \param[in,out] CY
65*> \verbatim
66*> CY is COMPLEX*16 array, dimension (N)
67*> On input, the vector Y.
68*> On output, CY is overwritten with -CONJG(S)*X + C*Y.
69*> \endverbatim
70*>
71*> \param[in] INCY
72*> \verbatim
73*> INCY is INTEGER
74*> The increment between successive values of CY. INCX <> 0.
75*> \endverbatim
76*>
77*> \param[in] C
78*> \verbatim
79*> C is DOUBLE PRECISION
80*> \endverbatim
81*>
82*> \param[in] S
83*> \verbatim
84*> S is COMPLEX*16
85*> C and S define a rotation
86*> [ C S ]
87*> [ -conjg(S) C ]
88*> where C*C + S*CONJG(S) = 1.0.
89*> \endverbatim
90*
91* Authors:
92* ========
93*
94*> \author Univ. of Tennessee
95*> \author Univ. of California Berkeley
96*> \author Univ. of Colorado Denver
97*> \author NAG Ltd.
98*
99*> \ingroup rot
100*
101* =====================================================================
102 SUBROUTINE zrot( N, CX, INCX, CY, INCY, C, S )
103*
104* -- LAPACK auxiliary routine --
105* -- LAPACK is a software package provided by Univ. of Tennessee, --
106* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
107*
108* .. Scalar Arguments ..
109 INTEGER INCX, INCY, N
110 DOUBLE PRECISION C
111 COMPLEX*16 S
112* ..
113* .. Array Arguments ..
114 COMPLEX*16 CX( * ), CY( * )
115* ..
116*
117* =====================================================================
118*
119* .. Local Scalars ..
120 INTEGER I, IX, IY
121 COMPLEX*16 STEMP
122* ..
123* .. Intrinsic Functions ..
124 INTRINSIC dconjg
125* ..
126* .. Executable Statements ..
127*
128 IF( n.LE.0 )
129 $ RETURN
130 IF( incx.EQ.1 .AND. incy.EQ.1 )
131 $ GO TO 20
132*
133* Code for unequal increments or equal increments not equal to 1
134*
135 ix = 1
136 iy = 1
137 IF( incx.LT.0 )
138 $ ix = ( -n+1 )*incx + 1
139 IF( incy.LT.0 )
140 $ iy = ( -n+1 )*incy + 1
141 DO 10 i = 1, n
142 stemp = c*cx( ix ) + s*cy( iy )
143 cy( iy ) = c*cy( iy ) - dconjg( s )*cx( ix )
144 cx( ix ) = stemp
145 ix = ix + incx
146 iy = iy + incy
147 10 CONTINUE
148 RETURN
149*
150* Code for both increments equal to 1
151*
152 20 CONTINUE
153 DO 30 i = 1, n
154 stemp = c*cx( i ) + s*cy( i )
155 cy( i ) = c*cy( i ) - dconjg( s )*cx( i )
156 cx( i ) = stemp
157 30 CONTINUE
158 RETURN
159 END
subroutine zrot(n, cx, incx, cy, incy, c, s)
ZROT applies a plane rotation with real cosine and complex sine to a pair of complex vectors.
Definition zrot.f:103