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