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.

clargv.f 8.9 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296
  1. *> \brief \b CLARGV 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 CLARGV + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clargv.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clargv.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clargv.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE CLARGV( N, X, INCX, Y, INCY, C, INCC )
  22. *
  23. * .. Scalar Arguments ..
  24. * INTEGER INCC, INCX, INCY, N
  25. * ..
  26. * .. Array Arguments ..
  27. * REAL C( * )
  28. * COMPLEX X( * ), Y( * )
  29. * ..
  30. *
  31. *
  32. *> \par Purpose:
  33. * =============
  34. *>
  35. *> \verbatim
  36. *>
  37. *> CLARGV 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 CLARTG,
  47. *> but differ from the BLAS1 routine CROTG):
  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 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 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 REAL 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. *> \ingroup complexOTHERauxiliary
  108. *
  109. *> \par Further Details:
  110. * =====================
  111. *>
  112. *> \verbatim
  113. *>
  114. *> 6-6-96 - Modified with a new algorithm by W. Kahan and J. Demmel
  115. *>
  116. *> This version has a few statements commented out for thread safety
  117. *> (machine parameters are computed on each entry). 10 feb 03, SJH.
  118. *> \endverbatim
  119. *>
  120. * =====================================================================
  121. SUBROUTINE CLARGV( N, X, INCX, Y, INCY, C, INCC )
  122. *
  123. * -- LAPACK auxiliary routine --
  124. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  125. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  126. *
  127. * .. Scalar Arguments ..
  128. INTEGER INCC, INCX, INCY, N
  129. * ..
  130. * .. Array Arguments ..
  131. REAL C( * )
  132. COMPLEX X( * ), Y( * )
  133. * ..
  134. *
  135. * =====================================================================
  136. *
  137. * .. Parameters ..
  138. REAL TWO, ONE, ZERO
  139. PARAMETER ( TWO = 2.0E+0, ONE = 1.0E+0, ZERO = 0.0E+0 )
  140. COMPLEX CZERO
  141. PARAMETER ( CZERO = ( 0.0E+0, 0.0E+0 ) )
  142. * ..
  143. * .. Local Scalars ..
  144. * LOGICAL FIRST
  145. INTEGER COUNT, I, IC, IX, IY, J
  146. REAL CS, D, DI, DR, EPS, F2, F2S, G2, G2S, SAFMIN,
  147. $ SAFMN2, SAFMX2, SCALE
  148. COMPLEX F, FF, FS, G, GS, R, SN
  149. * ..
  150. * .. External Functions ..
  151. REAL SLAMCH, SLAPY2
  152. EXTERNAL SLAMCH, SLAPY2
  153. * ..
  154. * .. Intrinsic Functions ..
  155. INTRINSIC ABS, AIMAG, CMPLX, CONJG, INT, LOG, MAX, REAL,
  156. $ SQRT
  157. * ..
  158. * .. Statement Functions ..
  159. REAL ABS1, ABSSQ
  160. * ..
  161. * .. Save statement ..
  162. * SAVE FIRST, SAFMX2, SAFMIN, SAFMN2
  163. * ..
  164. * .. Data statements ..
  165. * DATA FIRST / .TRUE. /
  166. * ..
  167. * .. Statement Function definitions ..
  168. ABS1( FF ) = MAX( ABS( REAL( FF ) ), ABS( AIMAG( FF ) ) )
  169. ABSSQ( FF ) = REAL( FF )**2 + AIMAG( FF )**2
  170. * ..
  171. * .. Executable Statements ..
  172. *
  173. * IF( FIRST ) THEN
  174. * FIRST = .FALSE.
  175. SAFMIN = SLAMCH( 'S' )
  176. EPS = SLAMCH( 'E' )
  177. SAFMN2 = SLAMCH( 'B' )**INT( LOG( SAFMIN / EPS ) /
  178. $ LOG( SLAMCH( 'B' ) ) / TWO )
  179. SAFMX2 = ONE / SAFMN2
  180. * END IF
  181. IX = 1
  182. IY = 1
  183. IC = 1
  184. DO 60 I = 1, N
  185. F = X( IX )
  186. G = Y( IY )
  187. *
  188. * Use identical algorithm as in CLARTG
  189. *
  190. SCALE = MAX( ABS1( F ), ABS1( G ) )
  191. FS = F
  192. GS = G
  193. COUNT = 0
  194. IF( SCALE.GE.SAFMX2 ) THEN
  195. 10 CONTINUE
  196. COUNT = COUNT + 1
  197. FS = FS*SAFMN2
  198. GS = GS*SAFMN2
  199. SCALE = SCALE*SAFMN2
  200. IF( SCALE.GE.SAFMX2 .AND. COUNT .LT. 20 )
  201. $ GO TO 10
  202. ELSE IF( SCALE.LE.SAFMN2 ) THEN
  203. IF( G.EQ.CZERO ) THEN
  204. CS = ONE
  205. SN = CZERO
  206. R = F
  207. GO TO 50
  208. END IF
  209. 20 CONTINUE
  210. COUNT = COUNT - 1
  211. FS = FS*SAFMX2
  212. GS = GS*SAFMX2
  213. SCALE = SCALE*SAFMX2
  214. IF( SCALE.LE.SAFMN2 )
  215. $ GO TO 20
  216. END IF
  217. F2 = ABSSQ( FS )
  218. G2 = ABSSQ( GS )
  219. IF( F2.LE.MAX( G2, ONE )*SAFMIN ) THEN
  220. *
  221. * This is a rare case: F is very small.
  222. *
  223. IF( F.EQ.CZERO ) THEN
  224. CS = ZERO
  225. R = SLAPY2( REAL( G ), AIMAG( G ) )
  226. * Do complex/real division explicitly with two real
  227. * divisions
  228. D = SLAPY2( REAL( GS ), AIMAG( GS ) )
  229. SN = CMPLX( REAL( GS ) / D, -AIMAG( GS ) / D )
  230. GO TO 50
  231. END IF
  232. F2S = SLAPY2( REAL( FS ), AIMAG( FS ) )
  233. * G2 and G2S are accurate
  234. * G2 is at least SAFMIN, and G2S is at least SAFMN2
  235. G2S = SQRT( G2 )
  236. * Error in CS from underflow in F2S is at most
  237. * UNFL / SAFMN2 .lt. sqrt(UNFL*EPS) .lt. EPS
  238. * If MAX(G2,ONE)=G2, then F2 .lt. G2*SAFMIN,
  239. * and so CS .lt. sqrt(SAFMIN)
  240. * If MAX(G2,ONE)=ONE, then F2 .lt. SAFMIN
  241. * and so CS .lt. sqrt(SAFMIN)/SAFMN2 = sqrt(EPS)
  242. * Therefore, CS = F2S/G2S / sqrt( 1 + (F2S/G2S)**2 ) = F2S/G2S
  243. CS = F2S / G2S
  244. * Make sure abs(FF) = 1
  245. * Do complex/real division explicitly with 2 real divisions
  246. IF( ABS1( F ).GT.ONE ) THEN
  247. D = SLAPY2( REAL( F ), AIMAG( F ) )
  248. FF = CMPLX( REAL( F ) / D, AIMAG( F ) / D )
  249. ELSE
  250. DR = SAFMX2*REAL( F )
  251. DI = SAFMX2*AIMAG( F )
  252. D = SLAPY2( DR, DI )
  253. FF = CMPLX( DR / D, DI / D )
  254. END IF
  255. SN = FF*CMPLX( REAL( GS ) / G2S, -AIMAG( GS ) / G2S )
  256. R = CS*F + SN*G
  257. ELSE
  258. *
  259. * This is the most common case.
  260. * Neither F2 nor F2/G2 are less than SAFMIN
  261. * F2S cannot overflow, and it is accurate
  262. *
  263. F2S = SQRT( ONE+G2 / F2 )
  264. * Do the F2S(real)*FS(complex) multiply with two real
  265. * multiplies
  266. R = CMPLX( F2S*REAL( FS ), F2S*AIMAG( FS ) )
  267. CS = ONE / F2S
  268. D = F2 + G2
  269. * Do complex/real division explicitly with two real divisions
  270. SN = CMPLX( REAL( R ) / D, AIMAG( R ) / D )
  271. SN = SN*CONJG( GS )
  272. IF( COUNT.NE.0 ) THEN
  273. IF( COUNT.GT.0 ) THEN
  274. DO 30 J = 1, COUNT
  275. R = R*SAFMX2
  276. 30 CONTINUE
  277. ELSE
  278. DO 40 J = 1, -COUNT
  279. R = R*SAFMN2
  280. 40 CONTINUE
  281. END IF
  282. END IF
  283. END IF
  284. 50 CONTINUE
  285. C( IC ) = CS
  286. Y( IY ) = SN
  287. X( IX ) = R
  288. IC = IC + INCC
  289. IY = IY + INCY
  290. IX = IX + INCX
  291. 60 CONTINUE
  292. RETURN
  293. *
  294. * End of CLARGV
  295. *
  296. END