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