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