LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlargv.f
Go to the documentation of this file.
1*> \brief \b DLARGV generates a vector of plane rotations with real cosines and real sines.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLARGV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlargv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlargv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlargv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLARGV( N, X, INCX, Y, INCY, C, INCC )
20*
21* .. Scalar Arguments ..
22* INTEGER INCC, INCX, INCY, N
23* ..
24* .. Array Arguments ..
25* DOUBLE PRECISION C( * ), X( * ), Y( * )
26* ..
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> DLARGV generates a vector of real plane rotations, determined by
35*> elements of the real vectors x and y. For i = 1,2,...,n
36*>
37*> ( c(i) s(i) ) ( x(i) ) = ( a(i) )
38*> ( -s(i) c(i) ) ( y(i) ) = ( 0 )
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] N
45*> \verbatim
46*> N is INTEGER
47*> The number of plane rotations to be generated.
48*> \endverbatim
49*>
50*> \param[in,out] X
51*> \verbatim
52*> X is DOUBLE PRECISION array,
53*> dimension (1+(N-1)*INCX)
54*> On entry, the vector x.
55*> On exit, x(i) is overwritten by a(i), for i = 1,...,n.
56*> \endverbatim
57*>
58*> \param[in] INCX
59*> \verbatim
60*> INCX is INTEGER
61*> The increment between elements of X. INCX > 0.
62*> \endverbatim
63*>
64*> \param[in,out] Y
65*> \verbatim
66*> Y is DOUBLE PRECISION array,
67*> dimension (1+(N-1)*INCY)
68*> On entry, the vector y.
69*> On exit, the sines of the plane rotations.
70*> \endverbatim
71*>
72*> \param[in] INCY
73*> \verbatim
74*> INCY is INTEGER
75*> The increment between elements of Y. INCY > 0.
76*> \endverbatim
77*>
78*> \param[out] C
79*> \verbatim
80*> C is DOUBLE PRECISION array, dimension (1+(N-1)*INCC)
81*> The cosines of the plane rotations.
82*> \endverbatim
83*>
84*> \param[in] INCC
85*> \verbatim
86*> INCC is INTEGER
87*> The increment between elements of C. INCC > 0.
88*> \endverbatim
89*
90* Authors:
91* ========
92*
93*> \author Univ. of Tennessee
94*> \author Univ. of California Berkeley
95*> \author Univ. of Colorado Denver
96*> \author NAG Ltd.
97*
98*> \ingroup largv
99*
100* =====================================================================
101 SUBROUTINE dlargv( N, X, INCX, Y, INCY, C, INCC )
102*
103* -- LAPACK auxiliary routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 INTEGER INCC, INCX, INCY, N
109* ..
110* .. Array Arguments ..
111 DOUBLE PRECISION C( * ), X( * ), Y( * )
112* ..
113*
114* =====================================================================
115*
116* .. Parameters ..
117 DOUBLE PRECISION ZERO, ONE
118 parameter( zero = 0.0d+0, one = 1.0d+0 )
119* ..
120* .. Local Scalars ..
121 INTEGER I, IC, IX, IY
122 DOUBLE PRECISION F, G, T, TT
123* ..
124* .. Intrinsic Functions ..
125 INTRINSIC abs, sqrt
126* ..
127* .. Executable Statements ..
128*
129 ix = 1
130 iy = 1
131 ic = 1
132 DO 10 i = 1, n
133 f = x( ix )
134 g = y( iy )
135 IF( g.EQ.zero ) THEN
136 c( ic ) = one
137 ELSE IF( f.EQ.zero ) THEN
138 c( ic ) = zero
139 y( iy ) = one
140 x( ix ) = g
141 ELSE IF( abs( f ).GT.abs( g ) ) THEN
142 t = g / f
143 tt = sqrt( one+t*t )
144 c( ic ) = one / tt
145 y( iy ) = t*c( ic )
146 x( ix ) = f*tt
147 ELSE
148 t = f / g
149 tt = sqrt( one+t*t )
150 y( iy ) = one / tt
151 c( ic ) = t*y( iy )
152 x( ix ) = g*tt
153 END IF
154 ic = ic + incc
155 iy = iy + incy
156 ix = ix + incx
157 10 CONTINUE
158 RETURN
159*
160* End of DLARGV
161*
162 END
subroutine dlargv(n, x, incx, y, incy, c, incc)
DLARGV generates a vector of plane rotations with real cosines and real sines.
Definition dlargv.f:102