LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ clargv()

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.
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 119 of file clargv.f.

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