01:       SUBROUTINE CLARTV( N, X, INCX, Y, INCY, C, S, INCC )
02: *
03: *  -- LAPACK auxiliary routine (version 3.2) --
04: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
05: *     November 2006
06: *
07: *     .. Scalar Arguments ..
08:       INTEGER            INCC, INCX, INCY, N
09: *     ..
10: *     .. Array Arguments ..
11:       REAL               C( * )
12:       COMPLEX            S( * ), X( * ), Y( * )
13: *     ..
14: *
15: *  Purpose
16: *  =======
17: *
18: *  CLARTV applies a vector of complex plane rotations with real cosines
19: *  to elements of the complex vectors x and y. For i = 1,2,...,n
20: *
21: *     ( x(i) ) := (        c(i)   s(i) ) ( x(i) )
22: *     ( y(i) )    ( -conjg(s(i))  c(i) ) ( y(i) )
23: *
24: *  Arguments
25: *  =========
26: *
27: *  N       (input) INTEGER
28: *          The number of plane rotations to be applied.
29: *
30: *  X       (input/output) COMPLEX array, dimension (1+(N-1)*INCX)
31: *          The vector x.
32: *
33: *  INCX    (input) INTEGER
34: *          The increment between elements of X. INCX > 0.
35: *
36: *  Y       (input/output) COMPLEX array, dimension (1+(N-1)*INCY)
37: *          The vector y.
38: *
39: *  INCY    (input) INTEGER
40: *          The increment between elements of Y. INCY > 0.
41: *
42: *  C       (input) REAL array, dimension (1+(N-1)*INCC)
43: *          The cosines of the plane rotations.
44: *
45: *  S       (input) COMPLEX array, dimension (1+(N-1)*INCC)
46: *          The sines of the plane rotations.
47: *
48: *  INCC    (input) INTEGER
49: *          The increment between elements of C and S. INCC > 0.
50: *
51: *  =====================================================================
52: *
53: *     .. Local Scalars ..
54:       INTEGER            I, IC, IX, IY
55:       COMPLEX            XI, YI
56: *     ..
57: *     .. Intrinsic Functions ..
58:       INTRINSIC          CONJG
59: *     ..
60: *     .. Executable Statements ..
61: *
62:       IX = 1
63:       IY = 1
64:       IC = 1
65:       DO 10 I = 1, N
66:          XI = X( IX )
67:          YI = Y( IY )
68:          X( IX ) = C( IC )*XI + S( IC )*YI
69:          Y( IY ) = C( IC )*YI - CONJG( S( IC ) )*XI
70:          IX = IX + INCX
71:          IY = IY + INCY
72:          IC = IC + INCC
73:    10 CONTINUE
74:       RETURN
75: *
76: *     End of CLARTV
77: *
78:       END
79: