1       SUBROUTINE ZLAR2V( N, X, Y, Z, INCX, C, S, INCC )
 2 *
 3 *  -- LAPACK auxiliary routine (version 3.2) --
 4 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 5 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 6 *     November 2006
 7 *
 8 *     .. Scalar Arguments ..
 9       INTEGER            INCC, INCX, N
10 *     ..
11 *     .. Array Arguments ..
12       DOUBLE PRECISION   C( * )
13       COMPLEX*16         S( * ), X( * ), Y( * ), Z( * )
14 *     ..
15 *
16 *  Purpose
17 *  =======
18 *
19 *  ZLAR2V applies a vector of complex plane rotations with real cosines
20 *  from both sides to a sequence of 2-by-2 complex Hermitian matrices,
21 *  defined by the elements of the vectors x, y and z. For i = 1,2,...,n
22 *
23 *     (       x(i)  z(i) ) :=
24 *     ( conjg(z(i)) y(i) )
25 *
26 *       (  c(i) conjg(s(i)) ) (       x(i)  z(i) ) ( c(i) -conjg(s(i)) )
27 *       ( -s(i)       c(i)  ) ( conjg(z(i)) y(i) ) ( s(i)        c(i)  )
28 *
29 *  Arguments
30 *  =========
31 *
32 *  N       (input) INTEGER
33 *          The number of plane rotations to be applied.
34 *
35 *  X       (input/output) COMPLEX*16 array, dimension (1+(N-1)*INCX)
36 *          The vector x; the elements of x are assumed to be real.
37 *
38 *  Y       (input/output) COMPLEX*16 array, dimension (1+(N-1)*INCX)
39 *          The vector y; the elements of y are assumed to be real.
40 *
41 *  Z       (input/output) COMPLEX*16 array, dimension (1+(N-1)*INCX)
42 *          The vector z.
43 *
44 *  INCX    (input) INTEGER
45 *          The increment between elements of X, Y and Z. INCX > 0.
46 *
47 *  C       (input) DOUBLE PRECISION array, dimension (1+(N-1)*INCC)
48 *          The cosines of the plane rotations.
49 *
50 *  S       (input) COMPLEX*16 array, dimension (1+(N-1)*INCC)
51 *          The sines of the plane rotations.
52 *
53 *  INCC    (input) INTEGER
54 *          The increment between elements of C and S. INCC > 0.
55 *
56 *  =====================================================================
57 *
58 *     .. Local Scalars ..
59       INTEGER            I, IC, IX
60       DOUBLE PRECISION   CI, SII, SIR, T1I, T1R, T5, T6, XI, YI, ZII,
61      $                   ZIR
62       COMPLEX*16         SI, T2, T3, T4, ZI
63 *     ..
64 *     .. Intrinsic Functions ..
65       INTRINSIC          DBLEDCMPLXDCONJGDIMAG
66 *     ..
67 *     .. Executable Statements ..
68 *
69       IX = 1
70       IC = 1
71       DO 10 I = 1, N
72          XI = DBLE( X( IX ) )
73          YI = DBLE( Y( IX ) )
74          ZI = Z( IX )
75          ZIR = DBLE( ZI )
76          ZII = DIMAG( ZI )
77          CI = C( IC )
78          SI = S( IC )
79          SIR = DBLE( SI )
80          SII = DIMAG( SI )
81          T1R = SIR*ZIR - SII*ZII
82          T1I = SIR*ZII + SII*ZIR
83          T2 = CI*ZI
84          T3 = T2 - DCONJG( SI )*XI
85          T4 = DCONJG( T2 ) + SI*YI
86          T5 = CI*XI + T1R
87          T6 = CI*YI - T1R
88          X( IX ) = CI*T5 + ( SIR*DBLE( T4 )+SII*DIMAG( T4 ) )
89          Y( IX ) = CI*T6 - ( SIR*DBLE( T3 )-SII*DIMAG( T3 ) )
90          Z( IX ) = CI*T3 + DCONJG( SI )*DCMPLX( T6, T1I )
91          IX = IX + INCX
92          IC = IC + INCC
93    10 CONTINUE
94       RETURN
95 *
96 *     End of ZLAR2V
97 *
98       END