You can not select more than 25 topics Topics must start with a chinese character,a letter or number, can include dashes ('-') and can be up to 35 characters long.

zlargv.f 9.0 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300
  1. *> \brief \b ZLARGV generates a vector of plane rotations with real cosines and complex sines.
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download ZLARGV + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlargv.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlargv.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlargv.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE ZLARGV( N, X, INCX, Y, INCY, C, INCC )
  22. *
  23. * .. Scalar Arguments ..
  24. * INTEGER INCC, INCX, INCY, N
  25. * ..
  26. * .. Array Arguments ..
  27. * DOUBLE PRECISION C( * )
  28. * COMPLEX*16 X( * ), Y( * )
  29. * ..
  30. *
  31. *
  32. *> \par Purpose:
  33. * =============
  34. *>
  35. *> \verbatim
  36. *>
  37. *> ZLARGV generates a vector of complex plane rotations with real
  38. *> cosines, determined by elements of the complex vectors x and y.
  39. *> For i = 1,2,...,n
  40. *>
  41. *> ( c(i) s(i) ) ( x(i) ) = ( r(i) )
  42. *> ( -conjg(s(i)) c(i) ) ( y(i) ) = ( 0 )
  43. *>
  44. *> where c(i)**2 + ABS(s(i))**2 = 1
  45. *>
  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.
  50. *> \endverbatim
  51. *
  52. * Arguments:
  53. * ==========
  54. *
  55. *> \param[in] N
  56. *> \verbatim
  57. *> N is INTEGER
  58. *> The number of plane rotations to be generated.
  59. *> \endverbatim
  60. *>
  61. *> \param[in,out] X
  62. *> \verbatim
  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.
  66. *> \endverbatim
  67. *>
  68. *> \param[in] INCX
  69. *> \verbatim
  70. *> INCX is INTEGER
  71. *> The increment between elements of X. INCX > 0.
  72. *> \endverbatim
  73. *>
  74. *> \param[in,out] Y
  75. *> \verbatim
  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.
  79. *> \endverbatim
  80. *>
  81. *> \param[in] INCY
  82. *> \verbatim
  83. *> INCY is INTEGER
  84. *> The increment between elements of Y. INCY > 0.
  85. *> \endverbatim
  86. *>
  87. *> \param[out] C
  88. *> \verbatim
  89. *> C is DOUBLE PRECISION array, dimension (1+(N-1)*INCC)
  90. *> The cosines of the plane rotations.
  91. *> \endverbatim
  92. *>
  93. *> \param[in] INCC
  94. *> \verbatim
  95. *> INCC is INTEGER
  96. *> The increment between elements of C. INCC > 0.
  97. *> \endverbatim
  98. *
  99. * Authors:
  100. * ========
  101. *
  102. *> \author Univ. of Tennessee
  103. *> \author Univ. of California Berkeley
  104. *> \author Univ. of Colorado Denver
  105. *> \author NAG Ltd.
  106. *
  107. *> \date December 2016
  108. *
  109. *> \ingroup complex16OTHERauxiliary
  110. *
  111. *> \par Further Details:
  112. * =====================
  113. *>
  114. *> \verbatim
  115. *>
  116. *> 6-6-96 - Modified with a new algorithm by W. Kahan and J. Demmel
  117. *>
  118. *> This version has a few statements commented out for thread safety
  119. *> (machine parameters are computed on each entry). 10 feb 03, SJH.
  120. *> \endverbatim
  121. *>
  122. * =====================================================================
  123. SUBROUTINE ZLARGV( N, X, INCX, Y, INCY, C, INCC )
  124. *
  125. * -- LAPACK auxiliary routine (version 3.7.0) --
  126. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  127. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  128. * December 2016
  129. *
  130. * .. Scalar Arguments ..
  131. INTEGER INCC, INCX, INCY, N
  132. * ..
  133. * .. Array Arguments ..
  134. DOUBLE PRECISION C( * )
  135. COMPLEX*16 X( * ), Y( * )
  136. * ..
  137. *
  138. * =====================================================================
  139. *
  140. * .. Parameters ..
  141. DOUBLE PRECISION TWO, ONE, ZERO
  142. PARAMETER ( TWO = 2.0D+0, ONE = 1.0D+0, ZERO = 0.0D+0 )
  143. COMPLEX*16 CZERO
  144. PARAMETER ( CZERO = ( 0.0D+0, 0.0D+0 ) )
  145. * ..
  146. * .. Local Scalars ..
  147. * LOGICAL FIRST
  148. INTEGER COUNT, I, IC, IX, IY, J
  149. DOUBLE PRECISION CS, D, DI, DR, EPS, F2, F2S, G2, G2S, SAFMIN,
  150. $ SAFMN2, SAFMX2, SCALE
  151. COMPLEX*16 F, FF, FS, G, GS, R, SN
  152. * ..
  153. * .. External Functions ..
  154. DOUBLE PRECISION DLAMCH, DLAPY2
  155. EXTERNAL DLAMCH, DLAPY2
  156. * ..
  157. * .. Intrinsic Functions ..
  158. INTRINSIC ABS, DBLE, DCMPLX, DCONJG, DIMAG, INT, LOG,
  159. $ MAX, SQRT
  160. * ..
  161. * .. Statement Functions ..
  162. DOUBLE PRECISION 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( DBLE( FF ) ), ABS( DIMAG( FF ) ) )
  172. ABSSQ( FF ) = DBLE( FF )**2 + DIMAG( FF )**2
  173. * ..
  174. * .. Executable Statements ..
  175. *
  176. * IF( FIRST ) THEN
  177. * FIRST = .FALSE.
  178. SAFMIN = DLAMCH( 'S' )
  179. EPS = DLAMCH( 'E' )
  180. SAFMN2 = DLAMCH( 'B' )**INT( LOG( SAFMIN / EPS ) /
  181. $ LOG( DLAMCH( '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 ZLARTG
  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 .AND. COUNT .LT. 20 )
  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 = DLAPY2( DBLE( G ), DIMAG( G ) )
  229. * Do complex/real division explicitly with two real
  230. * divisions
  231. D = DLAPY2( DBLE( GS ), DIMAG( GS ) )
  232. SN = DCMPLX( DBLE( GS ) / D, -DIMAG( GS ) / D )
  233. GO TO 50
  234. END IF
  235. F2S = DLAPY2( DBLE( FS ), DIMAG( 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 = DLAPY2( DBLE( F ), DIMAG( F ) )
  251. FF = DCMPLX( DBLE( F ) / D, DIMAG( F ) / D )
  252. ELSE
  253. DR = SAFMX2*DBLE( F )
  254. DI = SAFMX2*DIMAG( F )
  255. D = DLAPY2( DR, DI )
  256. FF = DCMPLX( DR / D, DI / D )
  257. END IF
  258. SN = FF*DCMPLX( DBLE( GS ) / G2S, -DIMAG( 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 = DCMPLX( F2S*DBLE( FS ), F2S*DIMAG( FS ) )
  270. CS = ONE / F2S
  271. D = F2 + G2
  272. * Do complex/real division explicitly with two real divisions
  273. SN = DCMPLX( DBLE( R ) / D, DIMAG( R ) / D )
  274. SN = SN*DCONJG( 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 ZLARGV
  298. *
  299. END