LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
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 *> \date September 2012
101 *
102 *> \ingroup doubleOTHERauxiliary
103 *
104 * =====================================================================
105  SUBROUTINE dlargv( N, X, INCX, Y, INCY, C, INCC )
106 *
107 * -- LAPACK auxiliary routine (version 3.4.2) --
108 * -- LAPACK is a software package provided by Univ. of Tennessee, --
109 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
110 * September 2012
111 *
112 * .. Scalar Arguments ..
113  INTEGER incc, incx, incy, n
114 * ..
115 * .. Array Arguments ..
116  DOUBLE PRECISION c( * ), x( * ), y( * )
117 * ..
118 *
119 * =====================================================================
120 *
121 * .. Parameters ..
122  DOUBLE PRECISION zero, one
123  parameter( zero = 0.0d+0, one = 1.0d+0 )
124 * ..
125 * .. Local Scalars ..
126  INTEGER i, ic, ix, iy
127  DOUBLE PRECISION f, g, t, tt
128 * ..
129 * .. Intrinsic Functions ..
130  INTRINSIC abs, sqrt
131 * ..
132 * .. Executable Statements ..
133 *
134  ix = 1
135  iy = 1
136  ic = 1
137  DO 10 i = 1, n
138  f = x( ix )
139  g = y( iy )
140  IF( g.EQ.zero ) THEN
141  c( ic ) = one
142  ELSE IF( f.EQ.zero ) THEN
143  c( ic ) = zero
144  y( iy ) = one
145  x( ix ) = g
146  ELSE IF( abs( f ).GT.abs( g ) ) THEN
147  t = g / f
148  tt = sqrt( one+t*t )
149  c( ic ) = one / tt
150  y( iy ) = t*c( ic )
151  x( ix ) = f*tt
152  ELSE
153  t = f / g
154  tt = sqrt( one+t*t )
155  y( iy ) = one / tt
156  c( ic ) = t*y( iy )
157  x( ix ) = g*tt
158  END IF
159  ic = ic + incc
160  iy = iy + incy
161  ix = ix + incx
162  10 continue
163  return
164 *
165 * End of DLARGV
166 *
167  END