cbesy.f 10 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236
  1. *DECK CBESY
  2. SUBROUTINE CBESY (Z, FNU, KODE, N, CY, NZ, CWRK, IERR)
  3. C***BEGIN PROLOGUE CBESY
  4. C***PURPOSE Compute a sequence of the Bessel functions Y(a,z) for
  5. C complex argument z and real nonnegative orders a=b,b+1,
  6. C b+2,... where b>0. A scaling option is available to
  7. C help avoid overflow.
  8. C***LIBRARY SLATEC
  9. C***CATEGORY C10A4
  10. C***TYPE COMPLEX (CBESY-C, ZBESY-C)
  11. C***KEYWORDS BESSEL FUNCTIONS OF COMPLEX ARGUMENT,
  12. C BESSEL FUNCTIONS OF SECOND KIND, WEBER'S FUNCTION,
  13. C Y BESSEL FUNCTIONS
  14. C***AUTHOR Amos, D. E., (SNL)
  15. C***DESCRIPTION
  16. C
  17. C On KODE=1, CBESY computes an N member sequence of complex
  18. C Bessel functions CY(L)=Y(FNU+L-1,Z) for real nonnegative
  19. C orders FNU+L-1, L=1,...,N and complex Z in the cut plane
  20. C -pi<arg(Z)<=pi. On KODE=2, CBESY returns the scaled
  21. C functions
  22. C
  23. C CY(L) = exp(-abs(Y))*Y(FNU+L-1,Z), L=1,...,N, Y=Im(Z)
  24. C
  25. C which remove the exponential growth in both the upper and
  26. C lower half planes as Z goes to infinity. Definitions and
  27. C notation are found in the NBS Handbook of Mathematical
  28. C Functions (Ref. 1).
  29. C
  30. C Input
  31. C Z - Nonzero argument of type COMPLEX
  32. C FNU - Initial order of type REAL, FNU>=0
  33. C KODE - A parameter to indicate the scaling option
  34. C KODE=1 returns
  35. C CY(L)=Y(FNU+L-1,Z), L=1,...,N
  36. C =2 returns
  37. C CY(L)=Y(FNU+L-1,Z)*exp(-abs(Y)), L=1,...,N
  38. C where Y=Im(Z)
  39. C N - Number of terms in the sequence, N>=1
  40. C CWRK - A work vector of type COMPLEX and dimension N
  41. C
  42. C Output
  43. C CY - Result vector of type COMPLEX
  44. C NZ - Number of underflows set to zero
  45. C NZ=0 Normal return
  46. C NZ>0 CY(L)=0 for NZ values of L, usually on
  47. C KODE=2 (the underflows may not be in an
  48. C uninterrupted sequence)
  49. C IERR - Error flag
  50. C IERR=0 Normal return - COMPUTATION COMPLETED
  51. C IERR=1 Input error - NO COMPUTATION
  52. C IERR=2 Overflow - NO COMPUTATION
  53. C (abs(Z) too small and/or FNU+N-1
  54. C too large)
  55. C IERR=3 Precision warning - COMPUTATION COMPLETED
  56. C (Result has half precision or less
  57. C because abs(Z) or FNU+N-1 is large)
  58. C IERR=4 Precision error - NO COMPUTATION
  59. C (Result has no precision because
  60. C abs(Z) or FNU+N-1 is too large)
  61. C IERR=5 Algorithmic error - NO COMPUTATION
  62. C (Termination condition not met)
  63. C
  64. C *Long Description:
  65. C
  66. C The computation is carried out by the formula
  67. C
  68. C Y(a,z) = (H(1,a,z) - H(2,a,z))/(2*i)
  69. C
  70. C where the Hankel functions are computed as described in CBESH.
  71. C
  72. C For negative orders, the formula
  73. C
  74. C Y(-a,z) = Y(a,z)*cos(a*pi) + J(a,z)*sin(a*pi)
  75. C
  76. C can be used. However, for large orders close to half odd
  77. C integers the function changes radically. When a is a large
  78. C positive half odd integer, the magnitude of Y(-a,z)=J(a,z)*
  79. C sin(a*pi) is a large negative power of ten. But when a is
  80. C not a half odd integer, Y(a,z) dominates in magnitude with a
  81. C large positive power of ten and the most that the second term
  82. C can be reduced is by unit roundoff from the coefficient.
  83. C Thus, wide changes can occur within unit roundoff of a large
  84. C half odd integer. Here, large means a>abs(z).
  85. C
  86. C In most complex variable computation, one must evaluate ele-
  87. C mentary functions. When the magnitude of Z or FNU+N-1 is
  88. C large, losses of significance by argument reduction occur.
  89. C Consequently, if either one exceeds U1=SQRT(0.5/UR), then
  90. C losses exceeding half precision are likely and an error flag
  91. C IERR=3 is triggered where UR=R1MACH(4)=UNIT ROUNDOFF. Also,
  92. C if either is larger than U2=0.5/UR, then all significance is
  93. C lost and IERR=4. In order to use the INT function, arguments
  94. C must be further restricted not to exceed the largest machine
  95. C integer, U3=I1MACH(9). Thus, the magnitude of Z and FNU+N-1
  96. C is restricted by MIN(U2,U3). In IEEE arithmetic, U1,U2, and
  97. C U3 approximate 2.0E+3, 4.2E+6, 2.1E+9 in single precision
  98. C and 4.7E+7, 2.3E+15 and 2.1E+9 in double precision. This
  99. C makes U2 limiting in single precision and U3 limiting in
  100. C double precision. This means that one can expect to retain,
  101. C in the worst cases on IEEE machines, no digits in single pre-
  102. C cision and only 6 digits in double precision. Similar con-
  103. C siderations hold for other machines.
  104. C
  105. C The approximate relative error in the magnitude of a complex
  106. C Bessel function can be expressed as P*10**S where P=MAX(UNIT
  107. C ROUNDOFF,1.0E-18) is the nominal precision and 10**S repre-
  108. C sents the increase in error due to argument reduction in the
  109. C elementary functions. Here, S=MAX(1,ABS(LOG10(ABS(Z))),
  110. C ABS(LOG10(FNU))) approximately (i.e., S=MAX(1,ABS(EXPONENT OF
  111. C ABS(Z),ABS(EXPONENT OF FNU)) ). However, the phase angle may
  112. C have only absolute accuracy. This is most likely to occur
  113. C when one component (in magnitude) is larger than the other by
  114. C several orders of magnitude. If one component is 10**K larger
  115. C than the other, then one can expect only MAX(ABS(LOG10(P))-K,
  116. C 0) significant digits; or, stated another way, when K exceeds
  117. C the exponent of P, no significant digits remain in the smaller
  118. C component. However, the phase angle retains absolute accuracy
  119. C because, in complex arithmetic with precision P, the smaller
  120. C component will not (as a rule) decrease below P times the
  121. C magnitude of the larger component. In these extreme cases,
  122. C the principal phase angle is on the order of +P, -P, PI/2-P,
  123. C or -PI/2+P.
  124. C
  125. C***REFERENCES 1. M. Abramowitz and I. A. Stegun, Handbook of Mathe-
  126. C matical Functions, National Bureau of Standards
  127. C Applied Mathematics Series 55, U. S. Department
  128. C of Commerce, Tenth Printing (1972) or later.
  129. C 2. D. E. Amos, Computation of Bessel Functions of
  130. C Complex Argument, Report SAND83-0086, Sandia National
  131. C Laboratories, Albuquerque, NM, May 1983.
  132. C 3. D. E. Amos, Computation of Bessel Functions of
  133. C Complex Argument and Large Order, Report SAND83-0643,
  134. C Sandia National Laboratories, Albuquerque, NM, May
  135. C 1983.
  136. C 4. D. E. Amos, A Subroutine Package for Bessel Functions
  137. C of a Complex Argument and Nonnegative Order, Report
  138. C SAND85-1018, Sandia National Laboratory, Albuquerque,
  139. C NM, May 1985.
  140. C 5. D. E. Amos, A portable package for Bessel functions
  141. C of a complex argument and nonnegative order, ACM
  142. C Transactions on Mathematical Software, 12 (September
  143. C 1986), pp. 265-273.
  144. C
  145. C***ROUTINES CALLED CBESH, I1MACH, R1MACH
  146. C***REVISION HISTORY (YYMMDD)
  147. C 830501 DATE WRITTEN
  148. C 890801 REVISION DATE from Version 3.2
  149. C 910415 Prologue converted to Version 4.0 format. (BAB)
  150. C 920128 Category corrected. (WRB)
  151. C 920811 Prologue revised. (DWL)
  152. C***END PROLOGUE CBESY
  153. C
  154. COMPLEX CWRK, CY, C1, C2, EX, HCI, Z, ZU, ZV
  155. REAL ELIM, EY, FNU, R1, R2, TAY, XX, YY, R1MACH, R1M5, ASCLE,
  156. * RTOL, ATOL, TOL, AA, BB
  157. INTEGER I, IERR, K, KODE, K1, K2, N, NZ, NZ1, NZ2, I1MACH
  158. DIMENSION CY(N), CWRK(N)
  159. C***FIRST EXECUTABLE STATEMENT CBESY
  160. XX = REAL(Z)
  161. YY = AIMAG(Z)
  162. IERR = 0
  163. NZ=0
  164. IF (XX.EQ.0.0E0 .AND. YY.EQ.0.0E0) IERR=1
  165. IF (FNU.LT.0.0E0) IERR=1
  166. IF (KODE.LT.1 .OR. KODE.GT.2) IERR=1
  167. IF (N.LT.1) IERR=1
  168. IF (IERR.NE.0) RETURN
  169. HCI = CMPLX(0.0E0,0.5E0)
  170. CALL CBESH(Z, FNU, KODE, 1, N, CY, NZ1, IERR)
  171. IF (IERR.NE.0.AND.IERR.NE.3) GO TO 170
  172. CALL CBESH(Z, FNU, KODE, 2, N, CWRK, NZ2, IERR)
  173. IF (IERR.NE.0.AND.IERR.NE.3) GO TO 170
  174. NZ = MIN(NZ1,NZ2)
  175. IF (KODE.EQ.2) GO TO 60
  176. DO 50 I=1,N
  177. CY(I) = HCI*(CWRK(I)-CY(I))
  178. 50 CONTINUE
  179. RETURN
  180. 60 CONTINUE
  181. TOL = MAX(R1MACH(4),1.0E-18)
  182. K1 = I1MACH(12)
  183. K2 = I1MACH(13)
  184. K = MIN(ABS(K1),ABS(K2))
  185. R1M5 = R1MACH(5)
  186. C-----------------------------------------------------------------------
  187. C ELIM IS THE APPROXIMATE EXPONENTIAL UNDER- AND OVERFLOW LIMIT
  188. C-----------------------------------------------------------------------
  189. ELIM = 2.303E0*(K*R1M5-3.0E0)
  190. R1 = COS(XX)
  191. R2 = SIN(XX)
  192. EX = CMPLX(R1,R2)
  193. EY = 0.0E0
  194. TAY = ABS(YY+YY)
  195. IF (TAY.LT.ELIM) EY = EXP(-TAY)
  196. IF (YY.LT.0.0E0) GO TO 90
  197. C1 = EX*CMPLX(EY,0.0E0)
  198. C2 = CONJG(EX)
  199. 70 CONTINUE
  200. NZ = 0
  201. RTOL = 1.0E0/TOL
  202. ASCLE = R1MACH(1)*RTOL*1.0E+3
  203. DO 80 I=1,N
  204. C CY(I) = HCI*(C2*CWRK(I)-C1*CY(I))
  205. ZV = CWRK(I)
  206. AA=REAL(ZV)
  207. BB=AIMAG(ZV)
  208. ATOL=1.0E0
  209. IF (MAX(ABS(AA),ABS(BB)).GT.ASCLE) GO TO 75
  210. ZV = ZV*CMPLX(RTOL,0.0E0)
  211. ATOL = TOL
  212. 75 CONTINUE
  213. ZV = ZV*C2*HCI
  214. ZV = ZV*CMPLX(ATOL,0.0E0)
  215. ZU=CY(I)
  216. AA=REAL(ZU)
  217. BB=AIMAG(ZU)
  218. ATOL=1.0E0
  219. IF (MAX(ABS(AA),ABS(BB)).GT.ASCLE) GO TO 85
  220. ZU = ZU*CMPLX(RTOL,0.0E0)
  221. ATOL = TOL
  222. 85 CONTINUE
  223. ZU = ZU*C1*HCI
  224. ZU = ZU*CMPLX(ATOL,0.0E0)
  225. CY(I) = ZV - ZU
  226. IF (CY(I).EQ.CMPLX(0.0E0,0.0E0) .AND. EY.EQ.0.0E0) NZ = NZ + 1
  227. 80 CONTINUE
  228. RETURN
  229. 90 CONTINUE
  230. C1 = EX
  231. C2 = CONJG(EX)*CMPLX(EY,0.0E0)
  232. GO TO 70
  233. 170 CONTINUE
  234. NZ = 0
  235. RETURN
  236. END