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

◆ zlargv()

subroutine zlargv ( integer n,
complex*16, dimension( * ) x,
integer incx,
complex*16, dimension( * ) y,
integer incy,
double precision, dimension( * ) c,
integer incc )

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

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

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