zbesk.f 12 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287
  1. *DECK ZBESK
  2. SUBROUTINE ZBESK (ZR, ZI, FNU, KODE, N, CYR, CYI, NZ, IERR)
  3. C***BEGIN PROLOGUE ZBESK
  4. C***PURPOSE Compute a sequence of the Bessel functions K(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 C10B4
  10. C***TYPE COMPLEX (CBESK-C, ZBESK-C)
  11. C***KEYWORDS BESSEL FUNCTIONS OF COMPLEX ARGUMENT, K BESSEL FUNCTIONS,
  12. C MODIFIED BESSEL FUNCTIONS
  13. C***AUTHOR Amos, D. E., (SNL)
  14. C***DESCRIPTION
  15. C
  16. C ***A DOUBLE PRECISION ROUTINE***
  17. C On KODE=1, ZBESK computes an N member sequence of complex
  18. C Bessel functions CY(L)=K(FNU+L-1,Z) for real nonnegative
  19. C orders FNU+L-1, L=1,...,N and complex Z.NE.0 in the cut
  20. C plane -pi<arg(Z)<=pi where Z=ZR+i*ZI. On KODE=2, CBESJ
  21. C returns the scaled functions
  22. C
  23. C CY(L) = exp(Z)*K(FNU+L-1,Z), L=1,...,N
  24. C
  25. C which remove the exponential growth in both the left and
  26. C right 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 ZR - DOUBLE PRECISION real part of nonzero argument Z
  32. C ZI - DOUBLE PRECISION imag part of nonzero argument Z
  33. C FNU - DOUBLE PRECISION initial order, FNU>=0
  34. C KODE - A parameter to indicate the scaling option
  35. C KODE=1 returns
  36. C CY(L)=K(FNU+L-1,Z), L=1,...,N
  37. C =2 returns
  38. C CY(L)=K(FNU+L-1,Z)*EXP(Z), L=1,...,N
  39. C N - Number of terms in the sequence, N>=1
  40. C
  41. C Output
  42. C CYR - DOUBLE PRECISION real part of result vector
  43. C CYI - DOUBLE PRECISION imag part of result vector
  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 (if Re(Z)>0
  47. C then CY(L)=0 for L=1,...,NZ; in the
  48. C complementary half plane the underflows
  49. C may not be in an uninterrupted sequence)
  50. C IERR - Error flag
  51. C IERR=0 Normal return - COMPUTATION COMPLETED
  52. C IERR=1 Input error - NO COMPUTATION
  53. C IERR=2 Overflow - NO COMPUTATION
  54. C (abs(Z) too small and/or FNU+N-1
  55. C too large)
  56. C IERR=3 Precision warning - COMPUTATION COMPLETED
  57. C (Result has half precision or less
  58. C because abs(Z) or FNU+N-1 is large)
  59. C IERR=4 Precision error - NO COMPUTATION
  60. C (Result has no precision because
  61. C abs(Z) or FNU+N-1 is too large)
  62. C IERR=5 Algorithmic error - NO COMPUTATION
  63. C (Termination condition not met)
  64. C
  65. C *Long Description:
  66. C
  67. C Equations of the reference are implemented to compute K(a,z)
  68. C for small orders a and a+1 in the right half plane Re(z)>=0.
  69. C Forward recurrence generates higher orders. The formula
  70. C
  71. C K(a,z*exp((t)) = exp(-t)*K(a,z) - t*I(a,z), Re(z)>0
  72. C t = i*pi or -i*pi
  73. C
  74. C continues K to the left half plane.
  75. C
  76. C For large orders, K(a,z) is computed by means of its uniform
  77. C asymptotic expansion.
  78. C
  79. C For negative orders, the formula
  80. C
  81. C K(-a,z) = K(a,z)
  82. C
  83. C can be used.
  84. C
  85. C CBESK assumes that a significant digit sinh function is
  86. C available.
  87. C
  88. C In most complex variable computation, one must evaluate ele-
  89. C mentary functions. When the magnitude of Z or FNU+N-1 is
  90. C large, losses of significance by argument reduction occur.
  91. C Consequently, if either one exceeds U1=SQRT(0.5/UR), then
  92. C losses exceeding half precision are likely and an error flag
  93. C IERR=3 is triggered where UR=MAX(D1MACH(4),1.0D-18) is double
  94. C precision unit roundoff limited to 18 digits precision. Also,
  95. C if either is larger than U2=0.5/UR, then all significance is
  96. C lost and IERR=4. In order to use the INT function, arguments
  97. C must be further restricted not to exceed the largest machine
  98. C integer, U3=I1MACH(9). Thus, the magnitude of Z and FNU+N-1
  99. C is restricted by MIN(U2,U3). In IEEE arithmetic, U1,U2, and
  100. C U3 approximate 2.0E+3, 4.2E+6, 2.1E+9 in single precision
  101. C and 4.7E+7, 2.3E+15 and 2.1E+9 in double precision. This
  102. C makes U2 limiting in single precision and U3 limiting in
  103. C double precision. This means that one can expect to retain,
  104. C in the worst cases on IEEE machines, no digits in single pre-
  105. C cision and only 6 digits in double precision. Similar con-
  106. C siderations hold for other machines.
  107. C
  108. C The approximate relative error in the magnitude of a complex
  109. C Bessel function can be expressed as P*10**S where P=MAX(UNIT
  110. C ROUNDOFF,1.0E-18) is the nominal precision and 10**S repre-
  111. C sents the increase in error due to argument reduction in the
  112. C elementary functions. Here, S=MAX(1,ABS(LOG10(ABS(Z))),
  113. C ABS(LOG10(FNU))) approximately (i.e., S=MAX(1,ABS(EXPONENT OF
  114. C ABS(Z),ABS(EXPONENT OF FNU)) ). However, the phase angle may
  115. C have only absolute accuracy. This is most likely to occur
  116. C when one component (in magnitude) is larger than the other by
  117. C several orders of magnitude. If one component is 10**K larger
  118. C than the other, then one can expect only MAX(ABS(LOG10(P))-K,
  119. C 0) significant digits; or, stated another way, when K exceeds
  120. C the exponent of P, no significant digits remain in the smaller
  121. C component. However, the phase angle retains absolute accuracy
  122. C because, in complex arithmetic with precision P, the smaller
  123. C component will not (as a rule) decrease below P times the
  124. C magnitude of the larger component. In these extreme cases,
  125. C the principal phase angle is on the order of +P, -P, PI/2-P,
  126. C or -PI/2+P.
  127. C
  128. C***REFERENCES 1. M. Abramowitz and I. A. Stegun, Handbook of Mathe-
  129. C matical Functions, National Bureau of Standards
  130. C Applied Mathematics Series 55, U. S. Department
  131. C of Commerce, Tenth Printing (1972) or later.
  132. C 2. D. E. Amos, Computation of Bessel Functions of
  133. C Complex Argument, Report SAND83-0086, Sandia National
  134. C Laboratories, Albuquerque, NM, May 1983.
  135. C 3. D. E. Amos, Computation of Bessel Functions of
  136. C Complex Argument and Large Order, Report SAND83-0643,
  137. C Sandia National Laboratories, Albuquerque, NM, May
  138. C 1983.
  139. C 4. D. E. Amos, A Subroutine Package for Bessel Functions
  140. C of a Complex Argument and Nonnegative Order, Report
  141. C SAND85-1018, Sandia National Laboratory, Albuquerque,
  142. C NM, May 1985.
  143. C 5. D. E. Amos, A portable package for Bessel functions
  144. C of a complex argument and nonnegative order, ACM
  145. C Transactions on Mathematical Software, 12 (September
  146. C 1986), pp. 265-273.
  147. C
  148. C***ROUTINES CALLED D1MACH, I1MACH, ZABS, ZACON, ZBKNU, ZBUNK, ZUOIK
  149. C***REVISION HISTORY (YYMMDD)
  150. C 830501 DATE WRITTEN
  151. C 890801 REVISION DATE from Version 3.2
  152. C 910415 Prologue converted to Version 4.0 format. (BAB)
  153. C 920128 Category corrected. (WRB)
  154. C 920811 Prologue revised. (DWL)
  155. C***END PROLOGUE ZBESK
  156. C
  157. C COMPLEX CY,Z
  158. DOUBLE PRECISION AA, ALIM, ALN, ARG, AZ, CYI, CYR, DIG, ELIM, FN,
  159. * FNU, FNUL, RL, R1M5, TOL, UFL, ZI, ZR, D1MACH, ZABS, BB
  160. INTEGER IERR, K, KODE, K1, K2, MR, N, NN, NUF, NW, NZ, I1MACH
  161. DIMENSION CYR(N), CYI(N)
  162. EXTERNAL ZABS
  163. C***FIRST EXECUTABLE STATEMENT ZBESK
  164. IERR = 0
  165. NZ=0
  166. IF (ZI.EQ.0.0E0 .AND. ZR.EQ.0.0E0) IERR=1
  167. IF (FNU.LT.0.0D0) IERR=1
  168. IF (KODE.LT.1 .OR. KODE.GT.2) IERR=1
  169. IF (N.LT.1) IERR=1
  170. IF (IERR.NE.0) RETURN
  171. NN = N
  172. C-----------------------------------------------------------------------
  173. C SET PARAMETERS RELATED TO MACHINE CONSTANTS.
  174. C TOL IS THE APPROXIMATE UNIT ROUNDOFF LIMITED TO 1.0E-18.
  175. C ELIM IS THE APPROXIMATE EXPONENTIAL OVER- AND UNDERFLOW LIMIT.
  176. C EXP(-ELIM).LT.EXP(-ALIM)=EXP(-ELIM)/TOL AND
  177. C EXP(ELIM).GT.EXP(ALIM)=EXP(ELIM)*TOL ARE INTERVALS NEAR
  178. C UNDERFLOW AND OVERFLOW LIMITS WHERE SCALED ARITHMETIC IS DONE.
  179. C RL IS THE LOWER BOUNDARY OF THE ASYMPTOTIC EXPANSION FOR LARGE Z.
  180. C DIG = NUMBER OF BASE 10 DIGITS IN TOL = 10**(-DIG).
  181. C FNUL IS THE LOWER BOUNDARY OF THE ASYMPTOTIC SERIES FOR LARGE FNU
  182. C-----------------------------------------------------------------------
  183. TOL = MAX(D1MACH(4),1.0D-18)
  184. K1 = I1MACH(15)
  185. K2 = I1MACH(16)
  186. R1M5 = D1MACH(5)
  187. K = MIN(ABS(K1),ABS(K2))
  188. ELIM = 2.303D0*(K*R1M5-3.0D0)
  189. K1 = I1MACH(14) - 1
  190. AA = R1M5*K1
  191. DIG = MIN(AA,18.0D0)
  192. AA = AA*2.303D0
  193. ALIM = ELIM + MAX(-AA,-41.45D0)
  194. FNUL = 10.0D0 + 6.0D0*(DIG-3.0D0)
  195. RL = 1.2D0*DIG + 3.0D0
  196. C-----------------------------------------------------------------------
  197. C TEST FOR PROPER RANGE
  198. C-----------------------------------------------------------------------
  199. AZ = ZABS(ZR,ZI)
  200. FN = FNU + (NN-1)
  201. AA = 0.5D0/TOL
  202. BB = I1MACH(9)*0.5D0
  203. AA = MIN(AA,BB)
  204. IF (AZ.GT.AA) GO TO 260
  205. IF (FN.GT.AA) GO TO 260
  206. AA = SQRT(AA)
  207. IF (AZ.GT.AA) IERR=3
  208. IF (FN.GT.AA) IERR=3
  209. C-----------------------------------------------------------------------
  210. C OVERFLOW TEST ON THE LAST MEMBER OF THE SEQUENCE
  211. C-----------------------------------------------------------------------
  212. C UFL = EXP(-ELIM)
  213. UFL = D1MACH(1)*1.0D+3
  214. IF (AZ.LT.UFL) GO TO 180
  215. IF (FNU.GT.FNUL) GO TO 80
  216. IF (FN.LE.1.0D0) GO TO 60
  217. IF (FN.GT.2.0D0) GO TO 50
  218. IF (AZ.GT.TOL) GO TO 60
  219. ARG = 0.5D0*AZ
  220. ALN = -FN*LOG(ARG)
  221. IF (ALN.GT.ELIM) GO TO 180
  222. GO TO 60
  223. 50 CONTINUE
  224. CALL ZUOIK(ZR, ZI, FNU, KODE, 2, NN, CYR, CYI, NUF, TOL, ELIM,
  225. * ALIM)
  226. IF (NUF.LT.0) GO TO 180
  227. NZ = NZ + NUF
  228. NN = NN - NUF
  229. C-----------------------------------------------------------------------
  230. C HERE NN=N OR NN=0 SINCE NUF=0,NN, OR -1 ON RETURN FROM CUOIK
  231. C IF NUF=NN, THEN CY(I)=CZERO FOR ALL I
  232. C-----------------------------------------------------------------------
  233. IF (NN.EQ.0) GO TO 100
  234. 60 CONTINUE
  235. IF (ZR.LT.0.0D0) GO TO 70
  236. C-----------------------------------------------------------------------
  237. C RIGHT HALF PLANE COMPUTATION, REAL(Z).GE.0.
  238. C-----------------------------------------------------------------------
  239. CALL ZBKNU(ZR, ZI, FNU, KODE, NN, CYR, CYI, NW, TOL, ELIM, ALIM)
  240. IF (NW.LT.0) GO TO 200
  241. NZ=NW
  242. RETURN
  243. C-----------------------------------------------------------------------
  244. C LEFT HALF PLANE COMPUTATION
  245. C PI/2.LT.ARG(Z).LE.PI AND -PI.LT.ARG(Z).LT.-PI/2.
  246. C-----------------------------------------------------------------------
  247. 70 CONTINUE
  248. IF (NZ.NE.0) GO TO 180
  249. MR = 1
  250. IF (ZI.LT.0.0D0) MR = -1
  251. CALL ZACON(ZR, ZI, FNU, KODE, MR, NN, CYR, CYI, NW, RL, FNUL,
  252. * TOL, ELIM, ALIM)
  253. IF (NW.LT.0) GO TO 200
  254. NZ=NW
  255. RETURN
  256. C-----------------------------------------------------------------------
  257. C UNIFORM ASYMPTOTIC EXPANSIONS FOR FNU.GT.FNUL
  258. C-----------------------------------------------------------------------
  259. 80 CONTINUE
  260. MR = 0
  261. IF (ZR.GE.0.0D0) GO TO 90
  262. MR = 1
  263. IF (ZI.LT.0.0D0) MR = -1
  264. 90 CONTINUE
  265. CALL ZBUNK(ZR, ZI, FNU, KODE, MR, NN, CYR, CYI, NW, TOL, ELIM,
  266. * ALIM)
  267. IF (NW.LT.0) GO TO 200
  268. NZ = NZ + NW
  269. RETURN
  270. 100 CONTINUE
  271. IF (ZR.LT.0.0D0) GO TO 180
  272. RETURN
  273. 180 CONTINUE
  274. NZ = 0
  275. IERR=2
  276. RETURN
  277. 200 CONTINUE
  278. IF(NW.EQ.(-1)) GO TO 180
  279. NZ=0
  280. IERR=5
  281. RETURN
  282. 260 CONTINUE
  283. NZ=0
  284. IERR=4
  285. RETURN
  286. END