LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zlartg.f
Go to the documentation of this file.
1 *> \brief \b ZLARTG generates a plane rotation with real cosine and complex sine.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZLARTG + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlartg.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlartg.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlartg.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZLARTG( F, G, CS, SN, R )
22 *
23 * .. Scalar Arguments ..
24 * DOUBLE PRECISION CS
25 * COMPLEX*16 F, G, R, SN
26 * ..
27 *
28 *
29 *> \par Purpose:
30 * =============
31 *>
32 *> \verbatim
33 *>
34 *> ZLARTG generates a plane rotation so that
35 *>
36 *> [ CS SN ] [ F ] [ R ]
37 *> [ __ ] . [ ] = [ ] where CS**2 + |SN|**2 = 1.
38 *> [ -SN CS ] [ G ] [ 0 ]
39 *>
40 *> This is a faster version of the BLAS1 routine ZROTG, except for
41 *> the following differences:
42 *> F and G are unchanged on return.
43 *> If G=0, then CS=1 and SN=0.
44 *> If F=0, then CS=0 and SN is chosen so that R is real.
45 *> \endverbatim
46 *
47 * Arguments:
48 * ==========
49 *
50 *> \param[in] F
51 *> \verbatim
52 *> F is COMPLEX*16
53 *> The first component of vector to be rotated.
54 *> \endverbatim
55 *>
56 *> \param[in] G
57 *> \verbatim
58 *> G is COMPLEX*16
59 *> The second component of vector to be rotated.
60 *> \endverbatim
61 *>
62 *> \param[out] CS
63 *> \verbatim
64 *> CS is DOUBLE PRECISION
65 *> The cosine of the rotation.
66 *> \endverbatim
67 *>
68 *> \param[out] SN
69 *> \verbatim
70 *> SN is COMPLEX*16
71 *> The sine of the rotation.
72 *> \endverbatim
73 *>
74 *> \param[out] R
75 *> \verbatim
76 *> R is COMPLEX*16
77 *> The nonzero component of the rotated vector.
78 *> \endverbatim
79 *
80 * Authors:
81 * ========
82 *
83 *> \author Univ. of Tennessee
84 *> \author Univ. of California Berkeley
85 *> \author Univ. of Colorado Denver
86 *> \author NAG Ltd.
87 *
88 *> \date November 2013
89 *
90 *> \ingroup complex16OTHERauxiliary
91 *
92 *> \par Further Details:
93 * =====================
94 *>
95 *> \verbatim
96 *>
97 *> 3-5-96 - Modified with a new algorithm by W. Kahan and J. Demmel
98 *>
99 *> This version has a few statements commented out for thread safety
100 *> (machine parameters are computed on each entry). 10 feb 03, SJH.
101 *> \endverbatim
102 *>
103 * =====================================================================
104  SUBROUTINE zlartg( F, G, CS, SN, R )
105 *
106 * -- LAPACK auxiliary routine (version 3.5.0) --
107 * -- LAPACK is a software package provided by Univ. of Tennessee, --
108 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
109 * November 2013
110 *
111 * .. Scalar Arguments ..
112  DOUBLE PRECISION CS
113  COMPLEX*16 F, G, R, SN
114 * ..
115 *
116 * =====================================================================
117 *
118 * .. Parameters ..
119  DOUBLE PRECISION TWO, ONE, ZERO
120  parameter ( two = 2.0d+0, one = 1.0d+0, zero = 0.0d+0 )
121  COMPLEX*16 CZERO
122  parameter ( czero = ( 0.0d+0, 0.0d+0 ) )
123 * ..
124 * .. Local Scalars ..
125 * LOGICAL FIRST
126  INTEGER COUNT, I
127  DOUBLE PRECISION D, DI, DR, EPS, F2, F2S, G2, G2S, SAFMIN,
128  $ safmn2, safmx2, scale
129  COMPLEX*16 FF, FS, GS
130 * ..
131 * .. External Functions ..
132  DOUBLE PRECISION DLAMCH, DLAPY2
133  LOGICAL DISNAN
134  EXTERNAL dlamch, dlapy2, disnan
135 * ..
136 * .. Intrinsic Functions ..
137  INTRINSIC abs, dble, dcmplx, dconjg, dimag, int, log,
138  $ max, sqrt
139 * ..
140 * .. Statement Functions ..
141  DOUBLE PRECISION ABS1, ABSSQ
142 * ..
143 * .. Statement Function definitions ..
144  abs1( ff ) = max( abs( dble( ff ) ), abs( dimag( ff ) ) )
145  abssq( ff ) = dble( ff )**2 + dimag( ff )**2
146 * ..
147 * .. Executable Statements ..
148 *
149  safmin = dlamch( 'S' )
150  eps = dlamch( 'E' )
151  safmn2 = dlamch( 'B' )**int( log( safmin / eps ) /
152  $ log( dlamch( 'B' ) ) / two )
153  safmx2 = one / safmn2
154  scale = max( abs1( f ), abs1( g ) )
155  fs = f
156  gs = g
157  count = 0
158  IF( scale.GE.safmx2 ) THEN
159  10 CONTINUE
160  count = count + 1
161  fs = fs*safmn2
162  gs = gs*safmn2
163  scale = scale*safmn2
164  IF( scale.GE.safmx2 )
165  $ GO TO 10
166  ELSE IF( scale.LE.safmn2 ) THEN
167  IF( g.EQ.czero.OR.disnan( abs( g ) ) ) THEN
168  cs = one
169  sn = czero
170  r = f
171  RETURN
172  END IF
173  20 CONTINUE
174  count = count - 1
175  fs = fs*safmx2
176  gs = gs*safmx2
177  scale = scale*safmx2
178  IF( scale.LE.safmn2 )
179  $ GO TO 20
180  END IF
181  f2 = abssq( fs )
182  g2 = abssq( gs )
183  IF( f2.LE.max( g2, one )*safmin ) THEN
184 *
185 * This is a rare case: F is very small.
186 *
187  IF( f.EQ.czero ) THEN
188  cs = zero
189  r = dlapy2( dble( g ), dimag( g ) )
190 * Do complex/real division explicitly with two real divisions
191  d = dlapy2( dble( gs ), dimag( gs ) )
192  sn = dcmplx( dble( gs ) / d, -dimag( gs ) / d )
193  RETURN
194  END IF
195  f2s = dlapy2( dble( fs ), dimag( fs ) )
196 * G2 and G2S are accurate
197 * G2 is at least SAFMIN, and G2S is at least SAFMN2
198  g2s = sqrt( g2 )
199 * Error in CS from underflow in F2S is at most
200 * UNFL / SAFMN2 .lt. sqrt(UNFL*EPS) .lt. EPS
201 * If MAX(G2,ONE)=G2, then F2 .lt. G2*SAFMIN,
202 * and so CS .lt. sqrt(SAFMIN)
203 * If MAX(G2,ONE)=ONE, then F2 .lt. SAFMIN
204 * and so CS .lt. sqrt(SAFMIN)/SAFMN2 = sqrt(EPS)
205 * Therefore, CS = F2S/G2S / sqrt( 1 + (F2S/G2S)**2 ) = F2S/G2S
206  cs = f2s / g2s
207 * Make sure abs(FF) = 1
208 * Do complex/real division explicitly with 2 real divisions
209  IF( abs1( f ).GT.one ) THEN
210  d = dlapy2( dble( f ), dimag( f ) )
211  ff = dcmplx( dble( f ) / d, dimag( f ) / d )
212  ELSE
213  dr = safmx2*dble( f )
214  di = safmx2*dimag( f )
215  d = dlapy2( dr, di )
216  ff = dcmplx( dr / d, di / d )
217  END IF
218  sn = ff*dcmplx( dble( gs ) / g2s, -dimag( gs ) / g2s )
219  r = cs*f + sn*g
220  ELSE
221 *
222 * This is the most common case.
223 * Neither F2 nor F2/G2 are less than SAFMIN
224 * F2S cannot overflow, and it is accurate
225 *
226  f2s = sqrt( one+g2 / f2 )
227 * Do the F2S(real)*FS(complex) multiply with two real multiplies
228  r = dcmplx( f2s*dble( fs ), f2s*dimag( fs ) )
229  cs = one / f2s
230  d = f2 + g2
231 * Do complex/real division explicitly with two real divisions
232  sn = dcmplx( dble( r ) / d, dimag( r ) / d )
233  sn = sn*dconjg( gs )
234  IF( count.NE.0 ) THEN
235  IF( count.GT.0 ) THEN
236  DO 30 i = 1, count
237  r = r*safmx2
238  30 CONTINUE
239  ELSE
240  DO 40 i = 1, -count
241  r = r*safmn2
242  40 CONTINUE
243  END IF
244  END IF
245  END IF
246  RETURN
247 *
248 * End of ZLARTG
249 *
250  END
subroutine zlartg(F, G, CS, SN, R)
ZLARTG generates a plane rotation with real cosine and complex sine.
Definition: zlartg.f:105