LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlartv.f
Go to the documentation of this file.
1*> \brief \b ZLARTV applies a vector of plane rotations with real cosines and complex sines to the elements of a pair of vectors.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZLARTV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlartv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlartv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlartv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZLARTV( N, X, INCX, Y, INCY, C, S, INCC )
20*
21* .. Scalar Arguments ..
22* INTEGER INCC, INCX, INCY, N
23* ..
24* .. Array Arguments ..
25* DOUBLE PRECISION C( * )
26* COMPLEX*16 S( * ), X( * ), Y( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZLARTV applies a vector of complex plane rotations with real cosines
36*> to elements of the complex vectors x and y. For i = 1,2,...,n
37*>
38*> ( x(i) ) := ( c(i) s(i) ) ( x(i) )
39*> ( y(i) ) ( -conjg(s(i)) c(i) ) ( y(i) )
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] N
46*> \verbatim
47*> N is INTEGER
48*> The number of plane rotations to be applied.
49*> \endverbatim
50*>
51*> \param[in,out] X
52*> \verbatim
53*> X is COMPLEX*16 array, dimension (1+(N-1)*INCX)
54*> The vector x.
55*> \endverbatim
56*>
57*> \param[in] INCX
58*> \verbatim
59*> INCX is INTEGER
60*> The increment between elements of X. INCX > 0.
61*> \endverbatim
62*>
63*> \param[in,out] Y
64*> \verbatim
65*> Y is COMPLEX*16 array, dimension (1+(N-1)*INCY)
66*> The vector y.
67*> \endverbatim
68*>
69*> \param[in] INCY
70*> \verbatim
71*> INCY is INTEGER
72*> The increment between elements of Y. INCY > 0.
73*> \endverbatim
74*>
75*> \param[in] C
76*> \verbatim
77*> C is DOUBLE PRECISION array, dimension (1+(N-1)*INCC)
78*> The cosines of the plane rotations.
79*> \endverbatim
80*>
81*> \param[in] S
82*> \verbatim
83*> S is COMPLEX*16 array, dimension (1+(N-1)*INCC)
84*> The sines of the plane rotations.
85*> \endverbatim
86*>
87*> \param[in] INCC
88*> \verbatim
89*> INCC is INTEGER
90*> The increment between elements of C and S. INCC > 0.
91*> \endverbatim
92*
93* Authors:
94* ========
95*
96*> \author Univ. of Tennessee
97*> \author Univ. of California Berkeley
98*> \author Univ. of Colorado Denver
99*> \author NAG Ltd.
100*
101*> \ingroup lartv
102*
103* =====================================================================
104 SUBROUTINE zlartv( N, X, INCX, Y, INCY, C, S, INCC )
105*
106* -- LAPACK auxiliary routine --
107* -- LAPACK is a software package provided by Univ. of Tennessee, --
108* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
109*
110* .. Scalar Arguments ..
111 INTEGER INCC, INCX, INCY, N
112* ..
113* .. Array Arguments ..
114 DOUBLE PRECISION C( * )
115 COMPLEX*16 S( * ), X( * ), Y( * )
116* ..
117*
118* =====================================================================
119*
120* .. Local Scalars ..
121 INTEGER I, IC, IX, IY
122 COMPLEX*16 XI, YI
123* ..
124* .. Intrinsic Functions ..
125 INTRINSIC dconjg
126* ..
127* .. Executable Statements ..
128*
129 ix = 1
130 iy = 1
131 ic = 1
132 DO 10 i = 1, n
133 xi = x( ix )
134 yi = y( iy )
135 x( ix ) = c( ic )*xi + s( ic )*yi
136 y( iy ) = c( ic )*yi - dconjg( s( ic ) )*xi
137 ix = ix + incx
138 iy = iy + incy
139 ic = ic + incc
140 10 CONTINUE
141 RETURN
142*
143* End of ZLARTV
144*
145 END
subroutine zlartv(n, x, incx, y, incy, c, s, incc)
ZLARTV applies a vector of plane rotations with real cosines and complex sines to the elements of a p...
Definition zlartv.f:105