LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zlargv.f
Go to the documentation of this file.
1 *> \brief \b ZLARGV generates a vector of plane rotations with real cosines and complex sines.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZLARGV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlargv.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlargv.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlargv.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZLARGV( 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( * )
28 * COMPLEX*16 X( * ), Y( * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> ZLARGV generates a vector of complex plane rotations with real
38 *> cosines, determined by elements of the complex vectors x and y.
39 *> For i = 1,2,...,n
40 *>
41 *> ( c(i) s(i) ) ( x(i) ) = ( r(i) )
42 *> ( -conjg(s(i)) c(i) ) ( y(i) ) = ( 0 )
43 *>
44 *> where c(i)**2 + ABS(s(i))**2 = 1
45 *>
46 *> The following conventions are used (these are the same as in ZLARTG,
47 *> but differ from the BLAS1 routine ZROTG):
48 *> If y(i)=0, then c(i)=1 and s(i)=0.
49 *> If x(i)=0, then c(i)=0 and s(i) is chosen so that r(i) is real.
50 *> \endverbatim
51 *
52 * Arguments:
53 * ==========
54 *
55 *> \param[in] N
56 *> \verbatim
57 *> N is INTEGER
58 *> The number of plane rotations to be generated.
59 *> \endverbatim
60 *>
61 *> \param[in,out] X
62 *> \verbatim
63 *> X is COMPLEX*16 array, dimension (1+(N-1)*INCX)
64 *> On entry, the vector x.
65 *> On exit, x(i) is overwritten by r(i), for i = 1,...,n.
66 *> \endverbatim
67 *>
68 *> \param[in] INCX
69 *> \verbatim
70 *> INCX is INTEGER
71 *> The increment between elements of X. INCX > 0.
72 *> \endverbatim
73 *>
74 *> \param[in,out] Y
75 *> \verbatim
76 *> Y is COMPLEX*16 array, dimension (1+(N-1)*INCY)
77 *> On entry, the vector y.
78 *> On exit, the sines of the plane rotations.
79 *> \endverbatim
80 *>
81 *> \param[in] INCY
82 *> \verbatim
83 *> INCY is INTEGER
84 *> The increment between elements of Y. INCY > 0.
85 *> \endverbatim
86 *>
87 *> \param[out] C
88 *> \verbatim
89 *> C is DOUBLE PRECISION array, dimension (1+(N-1)*INCC)
90 *> The cosines of the plane rotations.
91 *> \endverbatim
92 *>
93 *> \param[in] INCC
94 *> \verbatim
95 *> INCC is INTEGER
96 *> The increment between elements of C. INCC > 0.
97 *> \endverbatim
98 *
99 * Authors:
100 * ========
101 *
102 *> \author Univ. of Tennessee
103 *> \author Univ. of California Berkeley
104 *> \author Univ. of Colorado Denver
105 *> \author NAG Ltd.
106 *
107 *> \date September 2012
108 *
109 *> \ingroup complex16OTHERauxiliary
110 *
111 *> \par Further Details:
112 * =====================
113 *>
114 *> \verbatim
115 *>
116 *> 6-6-96 - Modified with a new algorithm by W. Kahan and J. Demmel
117 *>
118 *> This version has a few statements commented out for thread safety
119 *> (machine parameters are computed on each entry). 10 feb 03, SJH.
120 *> \endverbatim
121 *>
122 * =====================================================================
123  SUBROUTINE zlargv( N, X, INCX, Y, INCY, C, INCC )
124 *
125 * -- LAPACK auxiliary routine (version 3.4.2) --
126 * -- LAPACK is a software package provided by Univ. of Tennessee, --
127 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
128 * September 2012
129 *
130 * .. Scalar Arguments ..
131  INTEGER INCC, INCX, INCY, N
132 * ..
133 * .. Array Arguments ..
134  DOUBLE PRECISION C( * )
135  COMPLEX*16 X( * ), Y( * )
136 * ..
137 *
138 * =====================================================================
139 *
140 * .. Parameters ..
141  DOUBLE PRECISION TWO, ONE, ZERO
142  parameter ( two = 2.0d+0, one = 1.0d+0, zero = 0.0d+0 )
143  COMPLEX*16 CZERO
144  parameter ( czero = ( 0.0d+0, 0.0d+0 ) )
145 * ..
146 * .. Local Scalars ..
147 * LOGICAL FIRST
148 
149  INTEGER COUNT, I, IC, IX, IY, J
150  DOUBLE PRECISION CS, D, DI, DR, EPS, F2, F2S, G2, G2S, SAFMIN,
151  $ safmn2, safmx2, scale
152  COMPLEX*16 F, FF, FS, G, GS, R, SN
153 * ..
154 * .. External Functions ..
155  DOUBLE PRECISION DLAMCH, DLAPY2
156  EXTERNAL dlamch, dlapy2
157 * ..
158 * .. Intrinsic Functions ..
159  INTRINSIC abs, dble, dcmplx, dconjg, dimag, int, log,
160  $ max, sqrt
161 * ..
162 * .. Statement Functions ..
163  DOUBLE PRECISION ABS1, ABSSQ
164 * ..
165 * .. Save statement ..
166 * SAVE FIRST, SAFMX2, SAFMIN, SAFMN2
167 * ..
168 * .. Data statements ..
169 * DATA FIRST / .TRUE. /
170 * ..
171 * .. Statement Function definitions ..
172  abs1( ff ) = max( abs( dble( ff ) ), abs( dimag( ff ) ) )
173  abssq( ff ) = dble( ff )**2 + dimag( ff )**2
174 * ..
175 * .. Executable Statements ..
176 *
177 * IF( FIRST ) THEN
178 * FIRST = .FALSE.
179  safmin = dlamch( 'S' )
180  eps = dlamch( 'E' )
181  safmn2 = dlamch( 'B' )**int( log( safmin / eps ) /
182  $ log( dlamch( 'B' ) ) / two )
183  safmx2 = one / safmn2
184 * END IF
185  ix = 1
186  iy = 1
187  ic = 1
188  DO 60 i = 1, n
189  f = x( ix )
190  g = y( iy )
191 *
192 * Use identical algorithm as in ZLARTG
193 *
194  scale = max( abs1( f ), abs1( g ) )
195  fs = f
196  gs = g
197  count = 0
198  IF( scale.GE.safmx2 ) THEN
199  10 CONTINUE
200  count = count + 1
201  fs = fs*safmn2
202  gs = gs*safmn2
203  scale = scale*safmn2
204  IF( scale.GE.safmx2 )
205  $ GO TO 10
206  ELSE IF( scale.LE.safmn2 ) THEN
207  IF( g.EQ.czero ) THEN
208  cs = one
209  sn = czero
210  r = f
211  GO TO 50
212  END IF
213  20 CONTINUE
214  count = count - 1
215  fs = fs*safmx2
216  gs = gs*safmx2
217  scale = scale*safmx2
218  IF( scale.LE.safmn2 )
219  $ GO TO 20
220  END IF
221  f2 = abssq( fs )
222  g2 = abssq( gs )
223  IF( f2.LE.max( g2, one )*safmin ) THEN
224 *
225 * This is a rare case: F is very small.
226 *
227  IF( f.EQ.czero ) THEN
228  cs = zero
229  r = dlapy2( dble( g ), dimag( g ) )
230 * Do complex/real division explicitly with two real
231 * divisions
232  d = dlapy2( dble( gs ), dimag( gs ) )
233  sn = dcmplx( dble( gs ) / d, -dimag( gs ) / d )
234  GO TO 50
235  END IF
236  f2s = dlapy2( dble( fs ), dimag( fs ) )
237 * G2 and G2S are accurate
238 * G2 is at least SAFMIN, and G2S is at least SAFMN2
239  g2s = sqrt( g2 )
240 * Error in CS from underflow in F2S is at most
241 * UNFL / SAFMN2 .lt. sqrt(UNFL*EPS) .lt. EPS
242 * If MAX(G2,ONE)=G2, then F2 .lt. G2*SAFMIN,
243 * and so CS .lt. sqrt(SAFMIN)
244 * If MAX(G2,ONE)=ONE, then F2 .lt. SAFMIN
245 * and so CS .lt. sqrt(SAFMIN)/SAFMN2 = sqrt(EPS)
246 * Therefore, CS = F2S/G2S / sqrt( 1 + (F2S/G2S)**2 ) = F2S/G2S
247  cs = f2s / g2s
248 * Make sure abs(FF) = 1
249 * Do complex/real division explicitly with 2 real divisions
250  IF( abs1( f ).GT.one ) THEN
251  d = dlapy2( dble( f ), dimag( f ) )
252  ff = dcmplx( dble( f ) / d, dimag( f ) / d )
253  ELSE
254  dr = safmx2*dble( f )
255  di = safmx2*dimag( f )
256  d = dlapy2( dr, di )
257  ff = dcmplx( dr / d, di / d )
258  END IF
259  sn = ff*dcmplx( dble( gs ) / g2s, -dimag( gs ) / g2s )
260  r = cs*f + sn*g
261  ELSE
262 *
263 * This is the most common case.
264 * Neither F2 nor F2/G2 are less than SAFMIN
265 * F2S cannot overflow, and it is accurate
266 *
267  f2s = sqrt( one+g2 / f2 )
268 * Do the F2S(real)*FS(complex) multiply with two real
269 * multiplies
270  r = dcmplx( f2s*dble( fs ), f2s*dimag( fs ) )
271  cs = one / f2s
272  d = f2 + g2
273 * Do complex/real division explicitly with two real divisions
274  sn = dcmplx( dble( r ) / d, dimag( r ) / d )
275  sn = sn*dconjg( gs )
276  IF( count.NE.0 ) THEN
277  IF( count.GT.0 ) THEN
278  DO 30 j = 1, count
279  r = r*safmx2
280  30 CONTINUE
281  ELSE
282  DO 40 j = 1, -count
283  r = r*safmn2
284  40 CONTINUE
285  END IF
286  END IF
287  END IF
288  50 CONTINUE
289  c( ic ) = cs
290  y( iy ) = sn
291  x( ix ) = r
292  ic = ic + incc
293  iy = iy + incy
294  ix = ix + incx
295  60 CONTINUE
296  RETURN
297 *
298 * End of ZLARGV
299 *
300  END
subroutine zlargv(N, X, INCX, Y, INCY, C, INCC)
ZLARGV generates a vector of plane rotations with real cosines and complex sines. ...
Definition: zlargv.f:124