LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine clargv ( integer  N,
complex, dimension( * )  X,
integer  INCX,
complex, dimension( * )  Y,
integer  INCY,
real, dimension( * )  C,
integer  INCC 
)

CLARGV generates a vector of plane rotations with real cosines and complex sines.

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

Purpose:
 CLARGV generates a vector of complex plane rotations with real
 cosines, determined by elements of the complex vectors x and y.
 For i = 1,2,...,n

    (        c(i)   s(i) ) ( x(i) ) = ( r(i) )
    ( -conjg(s(i))  c(i) ) ( y(i) ) = (   0  )

    where c(i)**2 + ABS(s(i))**2 = 1

 The following conventions are used (these are the same as in CLARTG,
 but differ from the BLAS1 routine CROTG):
    If y(i)=0, then c(i)=1 and s(i)=0.
    If x(i)=0, then c(i)=0 and s(i) is chosen so that r(i) is real.
Parameters
[in]N
          N is INTEGER
          The number of plane rotations to be generated.
[in,out]X
          X is COMPLEX array, dimension (1+(N-1)*INCX)
          On entry, the vector x.
          On exit, x(i) is overwritten by r(i), for i = 1,...,n.
[in]INCX
          INCX is INTEGER
          The increment between elements of X. INCX > 0.
[in,out]Y
          Y is COMPLEX array, dimension (1+(N-1)*INCY)
          On entry, the vector y.
          On exit, the sines of the plane rotations.
[in]INCY
          INCY is INTEGER
          The increment between elements of Y. INCY > 0.
[out]C
          C is REAL array, dimension (1+(N-1)*INCC)
          The cosines of the plane rotations.
[in]INCC
          INCC is INTEGER
          The increment between elements of C. INCC > 0.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012
Further Details:
  6-6-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 124 of file clargv.f.

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  REAL c( * )
135  COMPLEX x( * ), y( * )
136 * ..
137 *
138 * =====================================================================
139 *
140 * .. Parameters ..
141  REAL two, one, zero
142  parameter ( two = 2.0e+0, one = 1.0e+0, zero = 0.0e+0 )
143  COMPLEX czero
144  parameter ( czero = ( 0.0e+0, 0.0e+0 ) )
145 * ..
146 * .. Local Scalars ..
147 * LOGICAL FIRST
148  INTEGER count, i, ic, ix, iy, j
149  REAL cs, d, di, dr, eps, f2, f2s, g2, g2s, safmin,
150  $ safmn2, safmx2, scale
151  COMPLEX f, ff, fs, g, gs, r, sn
152 * ..
153 * .. External Functions ..
154  REAL slamch, slapy2
155  EXTERNAL slamch, slapy2
156 * ..
157 * .. Intrinsic Functions ..
158  INTRINSIC abs, aimag, cmplx, conjg, int, log, max, REAL,
159  $ sqrt
160 * ..
161 * .. Statement Functions ..
162  REAL abs1, abssq
163 * ..
164 * .. Save statement ..
165 * SAVE FIRST, SAFMX2, SAFMIN, SAFMN2
166 * ..
167 * .. Data statements ..
168 * DATA FIRST / .TRUE. /
169 * ..
170 * .. Statement Function definitions ..
171  abs1( ff ) = max( abs( REAL( FF ) ), abs( aimag( ff ) ) )
172  abssq( ff ) = REAL( ff )**2 + aimag( ff )**2
173 * ..
174 * .. Executable Statements ..
175 *
176 * IF( FIRST ) THEN
177 * FIRST = .FALSE.
178  safmin = slamch( 'S' )
179  eps = slamch( 'E' )
180  safmn2 = slamch( 'B' )**int( log( safmin / eps ) /
181  $ log( slamch( 'B' ) ) / two )
182  safmx2 = one / safmn2
183 * END IF
184  ix = 1
185  iy = 1
186  ic = 1
187  DO 60 i = 1, n
188  f = x( ix )
189  g = y( iy )
190 *
191 * Use identical algorithm as in CLARTG
192 *
193  scale = max( abs1( f ), abs1( g ) )
194  fs = f
195  gs = g
196  count = 0
197  IF( scale.GE.safmx2 ) THEN
198  10 CONTINUE
199  count = count + 1
200  fs = fs*safmn2
201  gs = gs*safmn2
202  scale = scale*safmn2
203  IF( scale.GE.safmx2 )
204  $ GO TO 10
205  ELSE IF( scale.LE.safmn2 ) THEN
206  IF( g.EQ.czero ) THEN
207  cs = one
208  sn = czero
209  r = f
210  GO TO 50
211  END IF
212  20 CONTINUE
213  count = count - 1
214  fs = fs*safmx2
215  gs = gs*safmx2
216  scale = scale*safmx2
217  IF( scale.LE.safmn2 )
218  $ GO TO 20
219  END IF
220  f2 = abssq( fs )
221  g2 = abssq( gs )
222  IF( f2.LE.max( g2, one )*safmin ) THEN
223 *
224 * This is a rare case: F is very small.
225 *
226  IF( f.EQ.czero ) THEN
227  cs = zero
228  r = slapy2( REAL( G ), aimag( g ) )
229 * Do complex/real division explicitly with two real
230 * divisions
231  d = slapy2( REAL( GS ), aimag( gs ) )
232  sn = cmplx( REAL( GS ) / d, -aimag( gs ) / d )
233  GO TO 50
234  END IF
235  f2s = slapy2( REAL( FS ), aimag( fs ) )
236 * G2 and G2S are accurate
237 * G2 is at least SAFMIN, and G2S is at least SAFMN2
238  g2s = sqrt( g2 )
239 * Error in CS from underflow in F2S is at most
240 * UNFL / SAFMN2 .lt. sqrt(UNFL*EPS) .lt. EPS
241 * If MAX(G2,ONE)=G2, then F2 .lt. G2*SAFMIN,
242 * and so CS .lt. sqrt(SAFMIN)
243 * If MAX(G2,ONE)=ONE, then F2 .lt. SAFMIN
244 * and so CS .lt. sqrt(SAFMIN)/SAFMN2 = sqrt(EPS)
245 * Therefore, CS = F2S/G2S / sqrt( 1 + (F2S/G2S)**2 ) = F2S/G2S
246  cs = f2s / g2s
247 * Make sure abs(FF) = 1
248 * Do complex/real division explicitly with 2 real divisions
249  IF( abs1( f ).GT.one ) THEN
250  d = slapy2( REAL( F ), aimag( f ) )
251  ff = cmplx( REAL( F ) / d, aimag( f ) / d )
252  ELSE
253  dr = safmx2*REAL( f )
254  di = safmx2*aimag( f )
255  d = slapy2( dr, di )
256  ff = cmplx( dr / d, di / d )
257  END IF
258  sn = ff*cmplx( REAL( GS ) / g2s, -aimag( gs ) / g2s )
259  r = cs*f + sn*g
260  ELSE
261 *
262 * This is the most common case.
263 * Neither F2 nor F2/G2 are less than SAFMIN
264 * F2S cannot overflow, and it is accurate
265 *
266  f2s = sqrt( one+g2 / f2 )
267 * Do the F2S(real)*FS(complex) multiply with two real
268 * multiplies
269  r = cmplx( f2s*REAL( FS ), f2s*aimag( fs ) )
270  cs = one / f2s
271  d = f2 + g2
272 * Do complex/real division explicitly with two real divisions
273  sn = cmplx( REAL( R ) / d, aimag( r ) / d )
274  sn = sn*conjg( gs )
275  IF( count.NE.0 ) THEN
276  IF( count.GT.0 ) THEN
277  DO 30 j = 1, count
278  r = r*safmx2
279  30 CONTINUE
280  ELSE
281  DO 40 j = 1, -count
282  r = r*safmn2
283  40 CONTINUE
284  END IF
285  END IF
286  END IF
287  50 CONTINUE
288  c( ic ) = cs
289  y( iy ) = sn
290  x( ix ) = r
291  ic = ic + incc
292  iy = iy + incy
293  ix = ix + incx
294  60 CONTINUE
295  RETURN
296 *
297 * End of CLARGV
298 *
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: