cairy.f 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342
  1. *DECK CAIRY
  2. SUBROUTINE CAIRY (Z, ID, KODE, AI, NZ, IERR)
  3. C***BEGIN PROLOGUE CAIRY
  4. C***PURPOSE Compute the Airy function Ai(z) or its derivative dAi/dz
  5. C for complex argument z. A scaling option is available
  6. C to help avoid underflow and overflow.
  7. C***LIBRARY SLATEC
  8. C***CATEGORY C10D
  9. C***TYPE COMPLEX (CAIRY-C, ZAIRY-C)
  10. C***KEYWORDS AIRY FUNCTION, BESSEL FUNCTION OF ORDER ONE THIRD,
  11. C BESSEL FUNCTION OF ORDER TWO THIRDS
  12. C***AUTHOR Amos, D. E., (SNL)
  13. C***DESCRIPTION
  14. C
  15. C On KODE=1, CAIRY computes the complex Airy function Ai(z)
  16. C or its derivative dAi/dz on ID=0 or ID=1 respectively. On
  17. C KODE=2, a scaling option exp(zeta)*Ai(z) or exp(zeta)*dAi/dz
  18. C is provided to remove the exponential decay in -pi/3<arg(z)
  19. C <pi/3 and the exponential growth in pi/3<abs(arg(z))<pi where
  20. C zeta=(2/3)*z**(3/2).
  21. C
  22. C While the Airy functions Ai(z) and dAi/dz are analytic in
  23. C the whole z-plane, the corresponding scaled functions defined
  24. C for KODE=2 have a cut along the negative real axis.
  25. C
  26. C Input
  27. C Z - Argument of type COMPLEX
  28. C ID - Order of derivative, ID=0 or ID=1
  29. C KODE - A parameter to indicate the scaling option
  30. C KODE=1 returns
  31. C AI=Ai(z) on ID=0
  32. C AI=dAi/dz on ID=1
  33. C at z=Z
  34. C =2 returns
  35. C AI=exp(zeta)*Ai(z) on ID=0
  36. C AI=exp(zeta)*dAi/dz on ID=1
  37. C at z=Z where zeta=(2/3)*z**(3/2)
  38. C
  39. C Output
  40. C AI - Result of type COMPLEX
  41. C NZ - Underflow indicator
  42. C NZ=0 Normal return
  43. C NZ=1 AI=0 due to underflow in
  44. C -pi/3<arg(Z)<pi/3 on KODE=1
  45. C IERR - Error flag
  46. C IERR=0 Normal return - COMPUTATION COMPLETED
  47. C IERR=1 Input error - NO COMPUTATION
  48. C IERR=2 Overflow - NO COMPUTATION
  49. C (Re(Z) too large with KODE=1)
  50. C IERR=3 Precision warning - COMPUTATION COMPLETED
  51. C (Result has less than half precision)
  52. C IERR=4 Precision error - NO COMPUTATION
  53. C (Result has no precision)
  54. C IERR=5 Algorithmic error - NO COMPUTATION
  55. C (Termination condition not met)
  56. C
  57. C *Long Description:
  58. C
  59. C Ai(z) and dAi/dz are computed from K Bessel functions by
  60. C
  61. C Ai(z) = c*sqrt(z)*K(1/3,zeta)
  62. C dAi/dz = -c* z *K(2/3,zeta)
  63. C c = 1/(pi*sqrt(3))
  64. C zeta = (2/3)*z**(3/2)
  65. C
  66. C when abs(z)>1 and from power series when abs(z)<=1.
  67. C
  68. C In most complex variable computation, one must evaluate ele-
  69. C mentary functions. When the magnitude of Z is large, losses
  70. C of significance by argument reduction occur. Consequently, if
  71. C the magnitude of ZETA=(2/3)*Z**(3/2) exceeds U1=SQRT(0.5/UR),
  72. C then losses exceeding half precision are likely and an error
  73. C flag IERR=3 is triggered where UR=R1MACH(4)=UNIT ROUNDOFF.
  74. C Also, if the magnitude of ZETA is larger than U2=0.5/UR, then
  75. C all significance is lost and IERR=4. In order to use the INT
  76. C function, ZETA must be further restricted not to exceed
  77. C U3=I1MACH(9)=LARGEST INTEGER. Thus, the magnitude of ZETA
  78. C must be restricted by MIN(U2,U3). In IEEE arithmetic, U1,U2,
  79. C and U3 are approximately 2.0E+3, 4.2E+6, 2.1E+9 in single
  80. C precision and 4.7E+7, 2.3E+15, 2.1E+9 in double precision.
  81. C This makes U2 limiting is single precision and U3 limiting
  82. C in double precision. This means that the magnitude of Z
  83. C cannot exceed approximately 3.4E+4 in single precision and
  84. C 2.1E+6 in double precision. This also means that one can
  85. C expect to retain, in the worst cases on 32-bit machines,
  86. C no digits in single precision and only 6 digits in double
  87. C precision.
  88. C
  89. C The approximate relative error in the magnitude of a complex
  90. C Bessel function can be expressed as P*10**S where P=MAX(UNIT
  91. C ROUNDOFF,1.0E-18) is the nominal precision and 10**S repre-
  92. C sents the increase in error due to argument reduction in the
  93. C elementary functions. Here, S=MAX(1,ABS(LOG10(ABS(Z))),
  94. C ABS(LOG10(FNU))) approximately (i.e., S=MAX(1,ABS(EXPONENT OF
  95. C ABS(Z),ABS(EXPONENT OF FNU)) ). However, the phase angle may
  96. C have only absolute accuracy. This is most likely to occur
  97. C when one component (in magnitude) is larger than the other by
  98. C several orders of magnitude. If one component is 10**K larger
  99. C than the other, then one can expect only MAX(ABS(LOG10(P))-K,
  100. C 0) significant digits; or, stated another way, when K exceeds
  101. C the exponent of P, no significant digits remain in the smaller
  102. C component. However, the phase angle retains absolute accuracy
  103. C because, in complex arithmetic with precision P, the smaller
  104. C component will not (as a rule) decrease below P times the
  105. C magnitude of the larger component. In these extreme cases,
  106. C the principal phase angle is on the order of +P, -P, PI/2-P,
  107. C or -PI/2+P.
  108. C
  109. C***REFERENCES 1. M. Abramowitz and I. A. Stegun, Handbook of Mathe-
  110. C matical Functions, National Bureau of Standards
  111. C Applied Mathematics Series 55, U. S. Department
  112. C of Commerce, Tenth Printing (1972) or later.
  113. C 2. D. E. Amos, Computation of Bessel Functions of
  114. C Complex Argument and Large Order, Report SAND83-0643,
  115. C Sandia National Laboratories, Albuquerque, NM, May
  116. C 1983.
  117. C 3. D. E. Amos, A Subroutine Package for Bessel Functions
  118. C of a Complex Argument and Nonnegative Order, Report
  119. C SAND85-1018, Sandia National Laboratory, Albuquerque,
  120. C NM, May 1985.
  121. C 4. D. E. Amos, A portable package for Bessel functions
  122. C of a complex argument and nonnegative order, ACM
  123. C Transactions on Mathematical Software, 12 (September
  124. C 1986), pp. 265-273.
  125. C
  126. C***ROUTINES CALLED CACAI, CBKNU, I1MACH, R1MACH
  127. C***REVISION HISTORY (YYMMDD)
  128. C 830501 DATE WRITTEN
  129. C 890801 REVISION DATE from Version 3.2
  130. C 910415 Prologue converted to Version 4.0 format. (BAB)
  131. C 920128 Category corrected. (WRB)
  132. C 920811 Prologue revised. (DWL)
  133. C***END PROLOGUE CAIRY
  134. COMPLEX AI, CONE, CSQ, CY, S1, S2, TRM1, TRM2, Z, ZTA, Z3
  135. REAL AA, AD, AK, ALIM, ATRM, AZ, AZ3, BK, CK, COEF, C1, C2, DIG,
  136. * DK, D1, D2, ELIM, FID, FNU, RL, R1M5, SFAC, TOL, TTH, ZI, ZR,
  137. * Z3I, Z3R, R1MACH, BB, ALAZ
  138. INTEGER ID, IERR, IFLAG, K, KODE, K1, K2, MR, NN, NZ, I1MACH
  139. DIMENSION CY(1)
  140. DATA TTH, C1, C2, COEF /6.66666666666666667E-01,
  141. * 3.55028053887817240E-01,2.58819403792806799E-01,
  142. * 1.83776298473930683E-01/
  143. DATA CONE / (1.0E0,0.0E0) /
  144. C***FIRST EXECUTABLE STATEMENT CAIRY
  145. IERR = 0
  146. NZ=0
  147. IF (ID.LT.0 .OR. ID.GT.1) IERR=1
  148. IF (KODE.LT.1 .OR. KODE.GT.2) IERR=1
  149. IF (IERR.NE.0) RETURN
  150. AZ = ABS(Z)
  151. TOL = MAX(R1MACH(4),1.0E-18)
  152. FID = ID
  153. IF (AZ.GT.1.0E0) GO TO 60
  154. C-----------------------------------------------------------------------
  155. C POWER SERIES FOR ABS(Z).LE.1.
  156. C-----------------------------------------------------------------------
  157. S1 = CONE
  158. S2 = CONE
  159. IF (AZ.LT.TOL) GO TO 160
  160. AA = AZ*AZ
  161. IF (AA.LT.TOL/AZ) GO TO 40
  162. TRM1 = CONE
  163. TRM2 = CONE
  164. ATRM = 1.0E0
  165. Z3 = Z*Z*Z
  166. AZ3 = AZ*AA
  167. AK = 2.0E0 + FID
  168. BK = 3.0E0 - FID - FID
  169. CK = 4.0E0 - FID
  170. DK = 3.0E0 + FID + FID
  171. D1 = AK*DK
  172. D2 = BK*CK
  173. AD = MIN(D1,D2)
  174. AK = 24.0E0 + 9.0E0*FID
  175. BK = 30.0E0 - 9.0E0*FID
  176. Z3R = REAL(Z3)
  177. Z3I = AIMAG(Z3)
  178. DO 30 K=1,25
  179. TRM1 = TRM1*CMPLX(Z3R/D1,Z3I/D1)
  180. S1 = S1 + TRM1
  181. TRM2 = TRM2*CMPLX(Z3R/D2,Z3I/D2)
  182. S2 = S2 + TRM2
  183. ATRM = ATRM*AZ3/AD
  184. D1 = D1 + AK
  185. D2 = D2 + BK
  186. AD = MIN(D1,D2)
  187. IF (ATRM.LT.TOL*AD) GO TO 40
  188. AK = AK + 18.0E0
  189. BK = BK + 18.0E0
  190. 30 CONTINUE
  191. 40 CONTINUE
  192. IF (ID.EQ.1) GO TO 50
  193. AI = S1*CMPLX(C1,0.0E0) - Z*S2*CMPLX(C2,0.0E0)
  194. IF (KODE.EQ.1) RETURN
  195. ZTA = Z*CSQRT(Z)*CMPLX(TTH,0.0E0)
  196. AI = AI*CEXP(ZTA)
  197. RETURN
  198. 50 CONTINUE
  199. AI = -S2*CMPLX(C2,0.0E0)
  200. IF (AZ.GT.TOL) AI = AI + Z*Z*S1*CMPLX(C1/(1.0E0+FID),0.0E0)
  201. IF (KODE.EQ.1) RETURN
  202. ZTA = Z*CSQRT(Z)*CMPLX(TTH,0.0E0)
  203. AI = AI*CEXP(ZTA)
  204. RETURN
  205. C-----------------------------------------------------------------------
  206. C CASE FOR ABS(Z).GT.1.0
  207. C-----------------------------------------------------------------------
  208. 60 CONTINUE
  209. FNU = (1.0E0+FID)/3.0E0
  210. C-----------------------------------------------------------------------
  211. C SET PARAMETERS RELATED TO MACHINE CONSTANTS.
  212. C TOL IS THE APPROXIMATE UNIT ROUNDOFF LIMITED TO 1.0E-18.
  213. C ELIM IS THE APPROXIMATE EXPONENTIAL OVER- AND UNDERFLOW LIMIT.
  214. C EXP(-ELIM).LT.EXP(-ALIM)=EXP(-ELIM)/TOL AND
  215. C EXP(ELIM).GT.EXP(ALIM)=EXP(ELIM)*TOL ARE INTERVALS NEAR
  216. C UNDERFLOW AND OVERFLOW LIMITS WHERE SCALED ARITHMETIC IS DONE.
  217. C RL IS THE LOWER BOUNDARY OF THE ASYMPTOTIC EXPANSION FOR LARGE Z.
  218. C DIG = NUMBER OF BASE 10 DIGITS IN TOL = 10**(-DIG).
  219. C-----------------------------------------------------------------------
  220. K1 = I1MACH(12)
  221. K2 = I1MACH(13)
  222. R1M5 = R1MACH(5)
  223. K = MIN(ABS(K1),ABS(K2))
  224. ELIM = 2.303E0*(K*R1M5-3.0E0)
  225. K1 = I1MACH(11) - 1
  226. AA = R1M5*K1
  227. DIG = MIN(AA,18.0E0)
  228. AA = AA*2.303E0
  229. ALIM = ELIM + MAX(-AA,-41.45E0)
  230. RL = 1.2E0*DIG + 3.0E0
  231. ALAZ=ALOG(AZ)
  232. C-----------------------------------------------------------------------
  233. C TEST FOR RANGE
  234. C-----------------------------------------------------------------------
  235. AA=0.5E0/TOL
  236. BB=I1MACH(9)*0.5E0
  237. AA=MIN(AA,BB)
  238. AA=AA**TTH
  239. IF (AZ.GT.AA) GO TO 260
  240. AA=SQRT(AA)
  241. IF (AZ.GT.AA) IERR=3
  242. CSQ=CSQRT(Z)
  243. ZTA=Z*CSQ*CMPLX(TTH,0.0E0)
  244. C-----------------------------------------------------------------------
  245. C RE(ZTA).LE.0 WHEN RE(Z).LT.0, ESPECIALLY WHEN IM(Z) IS SMALL
  246. C-----------------------------------------------------------------------
  247. IFLAG = 0
  248. SFAC = 1.0E0
  249. ZI = AIMAG(Z)
  250. ZR = REAL(Z)
  251. AK = AIMAG(ZTA)
  252. IF (ZR.GE.0.0E0) GO TO 70
  253. BK = REAL(ZTA)
  254. CK = -ABS(BK)
  255. ZTA = CMPLX(CK,AK)
  256. 70 CONTINUE
  257. IF (ZI.NE.0.0E0) GO TO 80
  258. IF (ZR.GT.0.0E0) GO TO 80
  259. ZTA = CMPLX(0.0E0,AK)
  260. 80 CONTINUE
  261. AA = REAL(ZTA)
  262. IF (AA.GE.0.0E0 .AND. ZR.GT.0.0E0) GO TO 100
  263. IF (KODE.EQ.2) GO TO 90
  264. C-----------------------------------------------------------------------
  265. C OVERFLOW TEST
  266. C-----------------------------------------------------------------------
  267. IF (AA.GT.(-ALIM)) GO TO 90
  268. AA = -AA + 0.25E0*ALAZ
  269. IFLAG = 1
  270. SFAC = TOL
  271. IF (AA.GT.ELIM) GO TO 240
  272. 90 CONTINUE
  273. C-----------------------------------------------------------------------
  274. C CBKNU AND CACAI RETURN EXP(ZTA)*K(FNU,ZTA) ON KODE=2
  275. C-----------------------------------------------------------------------
  276. MR = 1
  277. IF (ZI.LT.0.0E0) MR = -1
  278. CALL CACAI(ZTA, FNU, KODE, MR, 1, CY, NN, RL, TOL, ELIM, ALIM)
  279. IF (NN.LT.0) GO TO 250
  280. NZ = NZ + NN
  281. GO TO 120
  282. 100 CONTINUE
  283. IF (KODE.EQ.2) GO TO 110
  284. C-----------------------------------------------------------------------
  285. C UNDERFLOW TEST
  286. C-----------------------------------------------------------------------
  287. IF (AA.LT.ALIM) GO TO 110
  288. AA = -AA - 0.25E0*ALAZ
  289. IFLAG = 2
  290. SFAC = 1.0E0/TOL
  291. IF (AA.LT.(-ELIM)) GO TO 180
  292. 110 CONTINUE
  293. CALL CBKNU(ZTA, FNU, KODE, 1, CY, NZ, TOL, ELIM, ALIM)
  294. 120 CONTINUE
  295. S1 = CY(1)*CMPLX(COEF,0.0E0)
  296. IF (IFLAG.NE.0) GO TO 140
  297. IF (ID.EQ.1) GO TO 130
  298. AI = CSQ*S1
  299. RETURN
  300. 130 AI = -Z*S1
  301. RETURN
  302. 140 CONTINUE
  303. S1 = S1*CMPLX(SFAC,0.0E0)
  304. IF (ID.EQ.1) GO TO 150
  305. S1 = S1*CSQ
  306. AI = S1*CMPLX(1.0E0/SFAC,0.0E0)
  307. RETURN
  308. 150 CONTINUE
  309. S1 = -S1*Z
  310. AI = S1*CMPLX(1.0E0/SFAC,0.0E0)
  311. RETURN
  312. 160 CONTINUE
  313. AA = 1.0E+3*R1MACH(1)
  314. S1 = CMPLX(0.0E0,0.0E0)
  315. IF (ID.EQ.1) GO TO 170
  316. IF (AZ.GT.AA) S1 = CMPLX(C2,0.0E0)*Z
  317. AI = CMPLX(C1,0.0E0) - S1
  318. RETURN
  319. 170 CONTINUE
  320. AI = -CMPLX(C2,0.0E0)
  321. AA = SQRT(AA)
  322. IF (AZ.GT.AA) S1 = Z*Z*CMPLX(0.5E0,0.0E0)
  323. AI = AI + S1*CMPLX(C1,0.0E0)
  324. RETURN
  325. 180 CONTINUE
  326. NZ = 1
  327. AI = CMPLX(0.0E0,0.0E0)
  328. RETURN
  329. 240 CONTINUE
  330. NZ = 0
  331. IERR=2
  332. RETURN
  333. 250 CONTINUE
  334. IF(NN.EQ.(-1)) GO TO 240
  335. NZ=0
  336. IERR=5
  337. RETURN
  338. 260 CONTINUE
  339. IERR=4
  340. NZ=0
  341. RETURN
  342. END