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