LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
drot.f
Go to the documentation of this file.
1*> \brief \b DROT
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE DROT(N,DX,INCX,DY,INCY,C,S)
12*
13* .. Scalar Arguments ..
14* DOUBLE PRECISION C,S
15* INTEGER INCX,INCY,N
16* ..
17* .. Array Arguments ..
18* DOUBLE PRECISION DX(*),DY(*)
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> DROT applies a plane rotation.
28*> \endverbatim
29*
30* Arguments:
31* ==========
32*
33*> \param[in] N
34*> \verbatim
35*> N is INTEGER
36*> number of elements in input vector(s)
37*> \endverbatim
38*>
39*> \param[in,out] DX
40*> \verbatim
41*> DX is DOUBLE PRECISION array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
42*> \endverbatim
43*>
44*> \param[in] INCX
45*> \verbatim
46*> INCX is INTEGER
47*> storage spacing between elements of DX
48*> \endverbatim
49*>
50*> \param[in,out] DY
51*> \verbatim
52*> DY is DOUBLE PRECISION array, dimension ( 1 + ( N - 1 )*abs( INCY ) )
53*> \endverbatim
54*>
55*> \param[in] INCY
56*> \verbatim
57*> INCY is INTEGER
58*> storage spacing between elements of DY
59*> \endverbatim
60*>
61*> \param[in] C
62*> \verbatim
63*> C is DOUBLE PRECISION
64*> \endverbatim
65*>
66*> \param[in] S
67*> \verbatim
68*> S is DOUBLE PRECISION
69*> \endverbatim
70*
71* Authors:
72* ========
73*
74*> \author Univ. of Tennessee
75*> \author Univ. of California Berkeley
76*> \author Univ. of Colorado Denver
77*> \author NAG Ltd.
78*
79*> \ingroup rot
80*
81*> \par Further Details:
82* =====================
83*>
84*> \verbatim
85*>
86*> jack dongarra, linpack, 3/11/78.
87*> modified 12/3/93, array(1) declarations changed to array(*)
88*> \endverbatim
89*>
90* =====================================================================
91 SUBROUTINE drot(N,DX,INCX,DY,INCY,C,S)
92*
93* -- Reference BLAS level1 routine --
94* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
95* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
96*
97* .. Scalar Arguments ..
98 DOUBLE PRECISION C,S
99 INTEGER INCX,INCY,N
100* ..
101* .. Array Arguments ..
102 DOUBLE PRECISION DX(*),DY(*)
103* ..
104*
105* =====================================================================
106*
107* .. Local Scalars ..
108 DOUBLE PRECISION DTEMP
109 INTEGER I,IX,IY
110* ..
111 IF (n.LE.0) RETURN
112 IF (incx.EQ.1 .AND. incy.EQ.1) THEN
113*
114* code for both increments equal to 1
115*
116 DO i = 1,n
117 dtemp = c*dx(i) + s*dy(i)
118 dy(i) = c*dy(i) - s*dx(i)
119 dx(i) = dtemp
120 END DO
121 ELSE
122*
123* code for unequal increments or equal increments not equal
124* to 1
125*
126 ix = 1
127 iy = 1
128 IF (incx.LT.0) ix = (-n+1)*incx + 1
129 IF (incy.LT.0) iy = (-n+1)*incy + 1
130 DO i = 1,n
131 dtemp = c*dx(ix) + s*dy(iy)
132 dy(iy) = c*dy(iy) - s*dx(ix)
133 dx(ix) = dtemp
134 ix = ix + incx
135 iy = iy + incy
136 END DO
137 END IF
138 RETURN
139*
140* End of DROT
141*
142 END
subroutine drot(n, dx, incx, dy, incy, c, s)
DROT
Definition drot.f:92