LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine clartg ( complex  F,
complex  G,
real  CS,
complex  SN,
complex  R 
)

CLARTG generates a plane rotation with real cosine and complex sine.

Download CLARTG + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 CLARTG generates a plane rotation so that

    [  CS  SN  ]     [ F ]     [ R ]
    [  __      ]  .  [   ]  =  [   ]   where CS**2 + |SN|**2 = 1.
    [ -SN  CS  ]     [ G ]     [ 0 ]

 This is a faster version of the BLAS1 routine CROTG, except for
 the following differences:
    F and G are unchanged on return.
    If G=0, then CS=1 and SN=0.
    If F=0, then CS=0 and SN is chosen so that R is real.
Parameters
[in]F
          F is COMPLEX
          The first component of vector to be rotated.
[in]G
          G is COMPLEX
          The second component of vector to be rotated.
[out]CS
          CS is REAL
          The cosine of the rotation.
[out]SN
          SN is COMPLEX
          The sine of the rotation.
[out]R
          R is COMPLEX
          The nonzero component of the rotated vector.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2013
Further Details:
  3-5-96 - Modified with a new algorithm by W. Kahan and J. Demmel

  This version has a few statements commented out for thread safety
  (machine parameters are computed on each entry). 10 feb 03, SJH.

Definition at line 105 of file clartg.f.

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  REAL cs
113  COMPLEX f, g, r, sn
114 * ..
115 *
116 * =====================================================================
117 *
118 * .. Parameters ..
119  REAL two, one, zero
120  parameter ( two = 2.0e+0, one = 1.0e+0, zero = 0.0e+0 )
121  COMPLEX czero
122  parameter ( czero = ( 0.0e+0, 0.0e+0 ) )
123 * ..
124 * .. Local Scalars ..
125 * LOGICAL FIRST
126  INTEGER count, i
127  REAL d, di, dr, eps, f2, f2s, g2, g2s, safmin,
128  $ safmn2, safmx2, scale
129  COMPLEX ff, fs, gs
130 * ..
131 * .. External Functions ..
132  REAL slamch, slapy2
133  LOGICAL sisnan
134  EXTERNAL slamch, slapy2, sisnan
135 * ..
136 * .. Intrinsic Functions ..
137  INTRINSIC abs, aimag, cmplx, conjg, int, log, max, REAL,
138  $ sqrt
139 * ..
140 * .. Statement Functions ..
141  REAL abs1, abssq
142 * ..
143 * .. Statement Function definitions ..
144  abs1( ff ) = max( abs( REAL( FF ) ), abs( aimag( ff ) ) )
145  abssq( ff ) = REAL( ff )**2 + aimag( ff )**2
146 * ..
147 * .. Executable Statements ..
148 *
149  safmin = slamch( 'S' )
150  eps = slamch( 'E' )
151  safmn2 = slamch( 'B' )**int( log( safmin / eps ) /
152  $ log( slamch( '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.sisnan( 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 = slapy2( REAL( G ), aimag( g ) )
190 * Do complex/real division explicitly with two real divisions
191  d = slapy2( REAL( GS ), aimag( gs ) )
192  sn = cmplx( REAL( GS ) / d, -aimag( gs ) / d )
193  RETURN
194  END IF
195  f2s = slapy2( REAL( FS ), aimag( 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 = slapy2( REAL( F ), aimag( f ) )
211  ff = cmplx( REAL( F ) / d, aimag( f ) / d )
212  ELSE
213  dr = safmx2*REAL( f )
214  di = safmx2*aimag( f )
215  d = slapy2( dr, di )
216  ff = cmplx( dr / d, di / d )
217  END IF
218  sn = ff*cmplx( REAL( GS ) / g2s, -aimag( 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 = cmplx( f2s*REAL( FS ), f2s*aimag( fs ) )
229  cs = one / f2s
230  d = f2 + g2
231 * Do complex/real division explicitly with two real divisions
232  sn = cmplx( REAL( R ) / d, aimag( r ) / d )
233  sn = sn*conjg( 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 CLARTG
249 *
logical function sisnan(SIN)
SISNAN tests input for NaN.
Definition: sisnan.f:61
real function slapy2(X, Y)
SLAPY2 returns sqrt(x2+y2).
Definition: slapy2.f:65
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69

Here is the caller graph for this function: