ENH: Improving the travis dashboard name
[platform/upstream/lapack.git] / SRC / clar2v.f
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 *> \date September 2012
108 *
109 *> \ingroup complexOTHERauxiliary
110 *
111 *  =====================================================================
112       SUBROUTINE CLAR2V( 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       REAL               C( * )
124       COMPLEX            S( * ), X( * ), Y( * ), Z( * )
125 *     ..
126 *
127 *  =====================================================================
128 *
129 *     .. Local Scalars ..
130       INTEGER            I, IC, IX
131       REAL               CI, SII, SIR, T1I, T1R, T5, T6, XI, YI, ZII,
132      $                   ZIR
133       COMPLEX            SI, T2, T3, T4, ZI
134 *     ..
135 *     .. Intrinsic Functions ..
136       INTRINSIC          AIMAG, CMPLX, CONJG, REAL
137 *     ..
138 *     .. Executable Statements ..
139 *
140       IX = 1
141       IC = 1
142       DO 10 I = 1, N
143          XI = REAL( X( IX ) )
144          YI = REAL( Y( IX ) )
145          ZI = Z( IX )
146          ZIR = REAL( ZI )
147          ZII = AIMAG( ZI )
148          CI = C( IC )
149          SI = S( IC )
150          SIR = REAL( SI )
151          SII = AIMAG( SI )
152          T1R = SIR*ZIR - SII*ZII
153          T1I = SIR*ZII + SII*ZIR
154          T2 = CI*ZI
155          T3 = T2 - CONJG( SI )*XI
156          T4 = CONJG( T2 ) + SI*YI
157          T5 = CI*XI + T1R
158          T6 = CI*YI - T1R
159          X( IX ) = CI*T5 + ( SIR*REAL( T4 )+SII*AIMAG( T4 ) )
160          Y( IX ) = CI*T6 - ( SIR*REAL( T3 )-SII*AIMAG( T3 ) )
161          Z( IX ) = CI*T3 + CONJG( SI )*CMPLX( T6, T1I )
162          IX = IX + INCX
163          IC = IC + INCC
164    10 CONTINUE
165       RETURN
166 *
167 *     End of CLAR2V
168 *
169       END