1 *> \brief \b ZLARGV generates a vector of plane rotations with real cosines and complex sines.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZLARGV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlargv.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlargv.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlargv.f">
21 * SUBROUTINE ZLARGV( N, X, INCX, Y, INCY, C, INCC )
23 * .. Scalar Arguments ..
24 * INTEGER INCC, INCX, INCY, N
26 * .. Array Arguments ..
27 * DOUBLE PRECISION C( * )
28 * COMPLEX*16 X( * ), Y( * )
37 *> ZLARGV generates a vector of complex plane rotations with real
38 *> cosines, determined by elements of the complex vectors x and y.
41 *> ( c(i) s(i) ) ( x(i) ) = ( r(i) )
42 *> ( -conjg(s(i)) c(i) ) ( y(i) ) = ( 0 )
44 *> where c(i)**2 + ABS(s(i))**2 = 1
46 *> The following conventions are used (these are the same as in ZLARTG,
47 *> but differ from the BLAS1 routine ZROTG):
48 *> If y(i)=0, then c(i)=1 and s(i)=0.
49 *> If x(i)=0, then c(i)=0 and s(i) is chosen so that r(i) is real.
58 *> The number of plane rotations to be generated.
63 *> X is COMPLEX*16 array, dimension (1+(N-1)*INCX)
64 *> On entry, the vector x.
65 *> On exit, x(i) is overwritten by r(i), for i = 1,...,n.
71 *> The increment between elements of X. INCX > 0.
76 *> Y is COMPLEX*16 array, dimension (1+(N-1)*INCY)
77 *> On entry, the vector y.
78 *> On exit, the sines of the plane rotations.
84 *> The increment between elements of Y. INCY > 0.
89 *> C is DOUBLE PRECISION array, dimension (1+(N-1)*INCC)
90 *> The cosines of the plane rotations.
96 *> The increment between elements of C. INCC > 0.
102 *> \author Univ. of Tennessee
103 *> \author Univ. of California Berkeley
104 *> \author Univ. of Colorado Denver
107 *> \date September 2012
109 *> \ingroup complex16OTHERauxiliary
111 *> \par Further Details:
112 * =====================
116 *> 6-6-96 - Modified with a new algorithm by W. Kahan and J. Demmel
118 *> This version has a few statements commented out for thread safety
119 *> (machine parameters are computed on each entry). 10 feb 03, SJH.
122 * =====================================================================
123 SUBROUTINE ZLARGV( N, X, INCX, Y, INCY, C, INCC )
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..--
130 * .. Scalar Arguments ..
131 INTEGER INCC, INCX, INCY, N
133 * .. Array Arguments ..
134 DOUBLE PRECISION C( * )
135 COMPLEX*16 X( * ), Y( * )
138 * =====================================================================
141 DOUBLE PRECISION TWO, ONE, ZERO
142 PARAMETER ( TWO = 2.0D+0, ONE = 1.0D+0, ZERO = 0.0D+0 )
144 PARAMETER ( CZERO = ( 0.0D+0, 0.0D+0 ) )
146 * .. Local Scalars ..
149 INTEGER COUNT, I, IC, IX, IY, J
150 DOUBLE PRECISION CS, D, DI, DR, EPS, F2, F2S, G2, G2S, SAFMIN,
151 $ SAFMN2, SAFMX2, SCALE
152 COMPLEX*16 F, FF, FS, G, GS, R, SN
154 * .. External Functions ..
155 DOUBLE PRECISION DLAMCH, DLAPY2
156 EXTERNAL DLAMCH, DLAPY2
158 * .. Intrinsic Functions ..
159 INTRINSIC ABS, DBLE, DCMPLX, DCONJG, DIMAG, INT, LOG,
162 * .. Statement Functions ..
163 DOUBLE PRECISION ABS1, ABSSQ
165 * .. Save statement ..
166 * SAVE FIRST, SAFMX2, SAFMIN, SAFMN2
168 * .. Data statements ..
169 * DATA FIRST / .TRUE. /
171 * .. Statement Function definitions ..
172 ABS1( FF ) = MAX( ABS( DBLE( FF ) ), ABS( DIMAG( FF ) ) )
173 ABSSQ( FF ) = DBLE( FF )**2 + DIMAG( FF )**2
175 * .. Executable Statements ..
179 SAFMIN = DLAMCH( 'S' )
181 SAFMN2 = DLAMCH( 'B' )**INT( LOG( SAFMIN / EPS ) /
182 $ LOG( DLAMCH( 'B' ) ) / TWO )
183 SAFMX2 = ONE / SAFMN2
192 * Use identical algorithm as in ZLARTG
194 SCALE = MAX( ABS1( F ), ABS1( G ) )
198 IF( SCALE.GE.SAFMX2 ) THEN
204 IF( SCALE.GE.SAFMX2 )
206 ELSE IF( SCALE.LE.SAFMN2 ) THEN
207 IF( G.EQ.CZERO ) THEN
218 IF( SCALE.LE.SAFMN2 )
223 IF( F2.LE.MAX( G2, ONE )*SAFMIN ) THEN
225 * This is a rare case: F is very small.
227 IF( F.EQ.CZERO ) THEN
229 R = DLAPY2( DBLE( G ), DIMAG( G ) )
230 * Do complex/real division explicitly with two real
232 D = DLAPY2( DBLE( GS ), DIMAG( GS ) )
233 SN = DCMPLX( DBLE( GS ) / D, -DIMAG( GS ) / D )
236 F2S = DLAPY2( DBLE( FS ), DIMAG( FS ) )
237 * G2 and G2S are accurate
238 * G2 is at least SAFMIN, and G2S is at least SAFMN2
240 * Error in CS from underflow in F2S is at most
241 * UNFL / SAFMN2 .lt. sqrt(UNFL*EPS) .lt. EPS
242 * If MAX(G2,ONE)=G2, then F2 .lt. G2*SAFMIN,
243 * and so CS .lt. sqrt(SAFMIN)
244 * If MAX(G2,ONE)=ONE, then F2 .lt. SAFMIN
245 * and so CS .lt. sqrt(SAFMIN)/SAFMN2 = sqrt(EPS)
246 * Therefore, CS = F2S/G2S / sqrt( 1 + (F2S/G2S)**2 ) = F2S/G2S
248 * Make sure abs(FF) = 1
249 * Do complex/real division explicitly with 2 real divisions
250 IF( ABS1( F ).GT.ONE ) THEN
251 D = DLAPY2( DBLE( F ), DIMAG( F ) )
252 FF = DCMPLX( DBLE( F ) / D, DIMAG( F ) / D )
254 DR = SAFMX2*DBLE( F )
255 DI = SAFMX2*DIMAG( F )
257 FF = DCMPLX( DR / D, DI / D )
259 SN = FF*DCMPLX( DBLE( GS ) / G2S, -DIMAG( GS ) / G2S )
263 * This is the most common case.
264 * Neither F2 nor F2/G2 are less than SAFMIN
265 * F2S cannot overflow, and it is accurate
267 F2S = SQRT( ONE+G2 / F2 )
268 * Do the F2S(real)*FS(complex) multiply with two real
270 R = DCMPLX( F2S*DBLE( FS ), F2S*DIMAG( FS ) )
273 * Do complex/real division explicitly with two real divisions
274 SN = DCMPLX( DBLE( R ) / D, DIMAG( R ) / D )
276 IF( COUNT.NE.0 ) THEN
277 IF( COUNT.GT.0 ) THEN