zbesy.f 11 KB

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