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