LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlacrt.f
Go to the documentation of this file.
1*> \brief \b ZLACRT performs a linear transformation of a pair of complex vectors.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZLACRT + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlacrt.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlacrt.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlacrt.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZLACRT( N, CX, INCX, CY, INCY, C, S )
20*
21* .. Scalar Arguments ..
22* INTEGER INCX, INCY, N
23* COMPLEX*16 C, S
24* ..
25* .. Array Arguments ..
26* COMPLEX*16 CX( * ), CY( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZLACRT performs the operation
36*>
37*> ( c s )( x ) ==> ( x )
38*> ( -s c )( y ) ( y )
39*>
40*> where c and s are complex and the vectors x and y are complex.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] N
47*> \verbatim
48*> N is INTEGER
49*> The number of elements in the vectors CX and CY.
50*> \endverbatim
51*>
52*> \param[in,out] CX
53*> \verbatim
54*> CX is COMPLEX*16 array, dimension (N)
55*> On input, the vector x.
56*> On output, CX is overwritten with c*x + s*y.
57*> \endverbatim
58*>
59*> \param[in] INCX
60*> \verbatim
61*> INCX is INTEGER
62*> The increment between successive values of CX. INCX <> 0.
63*> \endverbatim
64*>
65*> \param[in,out] CY
66*> \verbatim
67*> CY is COMPLEX*16 array, dimension (N)
68*> On input, the vector y.
69*> On output, CY is overwritten with -s*x + c*y.
70*> \endverbatim
71*>
72*> \param[in] INCY
73*> \verbatim
74*> INCY is INTEGER
75*> The increment between successive values of CY. INCY <> 0.
76*> \endverbatim
77*>
78*> \param[in] C
79*> \verbatim
80*> C is COMPLEX*16
81*> \endverbatim
82*>
83*> \param[in] S
84*> \verbatim
85*> S is COMPLEX*16
86*> C and S define the matrix
87*> [ C S ].
88*> [ -S C ]
89*> \endverbatim
90*
91* Authors:
92* ========
93*
94*> \author Univ. of Tennessee
95*> \author Univ. of California Berkeley
96*> \author Univ. of Colorado Denver
97*> \author NAG Ltd.
98*
99*> \ingroup lacrt
100*
101* =====================================================================
102 SUBROUTINE zlacrt( N, CX, INCX, CY, INCY, C, S )
103*
104* -- LAPACK auxiliary routine --
105* -- LAPACK is a software package provided by Univ. of Tennessee, --
106* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
107*
108* .. Scalar Arguments ..
109 INTEGER INCX, INCY, N
110 COMPLEX*16 C, S
111* ..
112* .. Array Arguments ..
113 COMPLEX*16 CX( * ), CY( * )
114* ..
115*
116* =====================================================================
117*
118* .. Local Scalars ..
119 INTEGER I, IX, IY
120 COMPLEX*16 CTEMP
121* ..
122* .. Executable Statements ..
123*
124 IF( n.LE.0 )
125 $ RETURN
126 IF( incx.EQ.1 .AND. incy.EQ.1 )
127 $ GO TO 20
128*
129* Code for unequal increments or equal increments not equal to 1
130*
131 ix = 1
132 iy = 1
133 IF( incx.LT.0 )
134 $ ix = ( -n+1 )*incx + 1
135 IF( incy.LT.0 )
136 $ iy = ( -n+1 )*incy + 1
137 DO 10 i = 1, n
138 ctemp = c*cx( ix ) + s*cy( iy )
139 cy( iy ) = c*cy( iy ) - s*cx( ix )
140 cx( ix ) = ctemp
141 ix = ix + incx
142 iy = iy + incy
143 10 CONTINUE
144 RETURN
145*
146* Code for both increments equal to 1
147*
148 20 CONTINUE
149 DO 30 i = 1, n
150 ctemp = c*cx( i ) + s*cy( i )
151 cy( i ) = c*cy( i ) - s*cx( i )
152 cx( i ) = ctemp
153 30 CONTINUE
154 RETURN
155 END
subroutine zlacrt(n, cx, incx, cy, incy, c, s)
ZLACRT performs a linear transformation of a pair of complex vectors.
Definition zlacrt.f:103