LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 *> \htmlonly
9 *> Download ZLAR2V + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlar2v.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlar2v.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlar2v.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZLAR2V( N, X, Y, Z, INCX, C, S, INCC )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER INCC, INCX, N
25 * ..
26 * .. Array Arguments ..
27 * DOUBLE PRECISION C( * )
28 * COMPLEX*16 S( * ), X( * ), Y( * ), Z( * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> ZLAR2V 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*16 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*16 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*16 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 DOUBLE PRECISION 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*16 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 *> \date September 2012
108 *
109 *> \ingroup complex16OTHERauxiliary
110 *
111 * =====================================================================
112  SUBROUTINE zlar2v( N, X, Y, Z, INCX, C, S, INCC )
113 *
114 * -- LAPACK auxiliary routine (version 3.4.2) --
115 * -- LAPACK is a software package provided by Univ. of Tennessee, --
116 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117 * September 2012
118 *
119 * .. Scalar Arguments ..
120  INTEGER INCC, INCX, N
121 * ..
122 * .. Array Arguments ..
123  DOUBLE PRECISION C( * )
124  COMPLEX*16 S( * ), X( * ), Y( * ), Z( * )
125 * ..
126 *
127 * =====================================================================
128 *
129 * .. Local Scalars ..
130  INTEGER I, IC, IX
131  DOUBLE PRECISION CI, SII, SIR, T1I, T1R, T5, T6, XI, YI, ZII,
132  $ zir
133  COMPLEX*16 SI, T2, T3, T4, ZI
134 * ..
135 * .. Intrinsic Functions ..
136  INTRINSIC dble, dcmplx, dconjg, dimag
137 * ..
138 * .. Executable Statements ..
139 *
140  ix = 1
141  ic = 1
142  DO 10 i = 1, n
143  xi = dble( x( ix ) )
144  yi = dble( y( ix ) )
145  zi = z( ix )
146  zir = dble( zi )
147  zii = dimag( zi )
148  ci = c( ic )
149  si = s( ic )
150  sir = dble( si )
151  sii = dimag( si )
152  t1r = sir*zir - sii*zii
153  t1i = sir*zii + sii*zir
154  t2 = ci*zi
155  t3 = t2 - dconjg( si )*xi
156  t4 = dconjg( t2 ) + si*yi
157  t5 = ci*xi + t1r
158  t6 = ci*yi - t1r
159  x( ix ) = ci*t5 + ( sir*dble( t4 )+sii*dimag( t4 ) )
160  y( ix ) = ci*t6 - ( sir*dble( t3 )-sii*dimag( t3 ) )
161  z( ix ) = ci*t3 + dconjg( si )*dcmplx( t6, t1i )
162  ix = ix + incx
163  ic = ic + incc
164  10 CONTINUE
165  RETURN
166 *
167 * End of ZLAR2V
168 *
169  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:113