PageRenderTime 47ms CodeModel.GetById 14ms RepoModel.GetById 1ms app.codeStats 0ms

/UAFWLIS2.4/slatec/cbiry.f

http://ua-fwlis.googlecode.com/
FORTRAN Legacy | 319 lines | 145 code | 0 blank | 174 comment | 0 complexity | 1e512a8f6199d24866e549b650242087 MD5 | raw file
Possible License(s): GPL-3.0
  1. *DECK CBIRY
  2. SUBROUTINE CBIRY (Z, ID, KODE, BI, IERR)
  3. C***BEGIN PROLOGUE CBIRY
  4. C***PURPOSE Compute the Airy function Bi(z) or its derivative dBi/dz
  5. C for complex argument z. A scaling option is available
  6. C to help avoid overflow.
  7. C***LIBRARY SLATEC
  8. C***CATEGORY C10D
  9. C***TYPE COMPLEX (CBIRY-C, ZBIRY-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, CBIRY computes the complex Airy function Bi(z)
  16. C or its derivative dBi/dz on ID=0 or ID=1 respectively.
  17. C On KODE=2, a scaling option exp(abs(Re(zeta)))*Bi(z) or
  18. C exp(abs(Re(zeta)))*dBi/dz is provided to remove the
  19. C exponential behavior in both the left and right half planes
  20. C where zeta=(2/3)*z**(3/2).
  21. C
  22. C The Airy functions Bi(z) and dBi/dz are analytic in the
  23. C whole z-plane, and the scaling option does not destroy this
  24. C property.
  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 BI=Bi(z) on ID=0
  32. C BI=dBi/dz on ID=1
  33. C at z=Z
  34. C =2 returns
  35. C BI=exp(abs(Re(zeta)))*Bi(z) on ID=0
  36. C BI=exp(abs(Re(zeta)))*dBi/dz on ID=1
  37. C at z=Z where zeta=(2/3)*z**(3/2)
  38. C
  39. C Output
  40. C BI - Result of type COMPLEX
  41. C IERR - Error flag
  42. C IERR=0 Normal return - COMPUTATION COMPLETED
  43. C IERR=1 Input error - NO COMPUTATION
  44. C IERR=2 Overflow - NO COMPUTATION
  45. C (Re(Z) too large with KODE=1)
  46. C IERR=3 Precision warning - COMPUTATION COMPLETED
  47. C (Result has less than half precision)
  48. C IERR=4 Precision error - NO COMPUTATION
  49. C (Result has no precision)
  50. C IERR=5 Algorithmic error - NO COMPUTATION
  51. C (Termination condition not met)
  52. C
  53. C *Long Description:
  54. C
  55. C Bi(z) and dBi/dz are computed from I Bessel functions by
  56. C
  57. C Bi(z) = c*sqrt(z)*( I(-1/3,zeta) + I(1/3,zeta) )
  58. C dBi/dz = c* z *( I(-2/3,zeta) + I(2/3,zeta) )
  59. C c = 1/sqrt(3)
  60. C zeta = (2/3)*z**(3/2)
  61. C
  62. C when abs(z)>1 and from power series when abs(z)<=1.
  63. C
  64. C In most complex variable computation, one must evaluate ele-
  65. C mentary functions. When the magnitude of Z is large, losses
  66. C of significance by argument reduction occur. Consequently, if
  67. C the magnitude of ZETA=(2/3)*Z**(3/2) exceeds U1=SQRT(0.5/UR),
  68. C then losses exceeding half precision are likely and an error
  69. C flag IERR=3 is triggered where UR=R1MACH(4)=UNIT ROUNDOFF.
  70. C Also, if the magnitude of ZETA is larger than U2=0.5/UR, then
  71. C all significance is lost and IERR=4. In order to use the INT
  72. C function, ZETA must be further restricted not to exceed
  73. C U3=I1MACH(9)=LARGEST INTEGER. Thus, the magnitude of ZETA
  74. C must be restricted by MIN(U2,U3). In IEEE arithmetic, U1,U2,
  75. C and U3 are approximately 2.0E+3, 4.2E+6, 2.1E+9 in single
  76. C precision and 4.7E+7, 2.3E+15, 2.1E+9 in double precision.
  77. C This makes U2 limiting is single precision and U3 limiting
  78. C in double precision. This means that the magnitude of Z
  79. C cannot exceed approximately 3.4E+4 in single precision and
  80. C 2.1E+6 in double precision. This also means that one can
  81. C expect to retain, in the worst cases on 32-bit machines,
  82. C no digits in single precision and only 6 digits in double
  83. C precision.
  84. C
  85. C The approximate relative error in the magnitude of a complex
  86. C Bessel function can be expressed as P*10**S where P=MAX(UNIT
  87. C ROUNDOFF,1.0E-18) is the nominal precision and 10**S repre-
  88. C sents the increase in error due to argument reduction in the
  89. C elementary functions. Here, S=MAX(1,ABS(LOG10(ABS(Z))),
  90. C ABS(LOG10(FNU))) approximately (i.e., S=MAX(1,ABS(EXPONENT OF
  91. C ABS(Z),ABS(EXPONENT OF FNU)) ). However, the phase angle may
  92. C have only absolute accuracy. This is most likely to occur
  93. C when one component (in magnitude) is larger than the other by
  94. C several orders of magnitude. If one component is 10**K larger
  95. C than the other, then one can expect only MAX(ABS(LOG10(P))-K,
  96. C 0) significant digits; or, stated another way, when K exceeds
  97. C the exponent of P, no significant digits remain in the smaller
  98. C component. However, the phase angle retains absolute accuracy
  99. C because, in complex arithmetic with precision P, the smaller
  100. C component will not (as a rule) decrease below P times the
  101. C magnitude of the larger component. In these extreme cases,
  102. C the principal phase angle is on the order of +P, -P, PI/2-P,
  103. C or -PI/2+P.
  104. C
  105. C***REFERENCES 1. M. Abramowitz and I. A. Stegun, Handbook of Mathe-
  106. C matical Functions, National Bureau of Standards
  107. C Applied Mathematics Series 55, U. S. Department
  108. C of Commerce, Tenth Printing (1972) or later.
  109. C 2. D. E. Amos, Computation of Bessel Functions of
  110. C Complex Argument and Large Order, Report SAND83-0643,
  111. C Sandia National Laboratories, Albuquerque, NM, May
  112. C 1983.
  113. C 3. D. E. Amos, A Subroutine Package for Bessel Functions
  114. C of a Complex Argument and Nonnegative Order, Report
  115. C SAND85-1018, Sandia National Laboratory, Albuquerque,
  116. C NM, May 1985.
  117. C 4. D. E. Amos, A portable package for Bessel functions
  118. C of a complex argument and nonnegative order, ACM
  119. C Transactions on Mathematical Software, 12 (September
  120. C 1986), pp. 265-273.
  121. C
  122. C***ROUTINES CALLED CBINU, I1MACH, R1MACH
  123. C***REVISION HISTORY (YYMMDD)
  124. C 830501 DATE WRITTEN
  125. C 890801 REVISION DATE from Version 3.2
  126. C 910415 Prologue converted to Version 4.0 format. (BAB)
  127. C 920128 Category corrected. (WRB)
  128. C 920811 Prologue revised. (DWL)
  129. C***END PROLOGUE CBIRY
  130. COMPLEX BI, CONE, CSQ, CY, S1, S2, TRM1, TRM2, Z, ZTA, Z3
  131. REAL AA, AD, AK, ALIM, ATRM, AZ, AZ3, BB, BK, CK, COEF, C1, C2,
  132. * DIG, DK, D1, D2, ELIM, FID, FMR, FNU, FNUL, PI, RL, R1M5, SFAC,
  133. * TOL, TTH, ZI, ZR, Z3I, Z3R, R1MACH
  134. INTEGER ID, IERR, K, KODE, K1, K2, NZ, I1MACH
  135. DIMENSION CY(2)
  136. DATA TTH, C1, C2, COEF, PI /6.66666666666666667E-01,
  137. * 6.14926627446000736E-01,4.48288357353826359E-01,
  138. * 5.77350269189625765E-01,3.14159265358979324E+00/
  139. DATA CONE / (1.0E0,0.0E0) /
  140. C***FIRST EXECUTABLE STATEMENT CBIRY
  141. IERR = 0
  142. NZ=0
  143. IF (ID.LT.0 .OR. ID.GT.1) IERR=1
  144. IF (KODE.LT.1 .OR. KODE.GT.2) IERR=1
  145. IF (IERR.NE.0) RETURN
  146. AZ = ABS(Z)
  147. TOL = MAX(R1MACH(4),1.0E-18)
  148. FID = ID
  149. IF (AZ.GT.1.0E0) GO TO 60
  150. C-----------------------------------------------------------------------
  151. C POWER SERIES FOR ABS(Z).LE.1.
  152. C-----------------------------------------------------------------------
  153. S1 = CONE
  154. S2 = CONE
  155. IF (AZ.LT.TOL) GO TO 110
  156. AA = AZ*AZ
  157. IF (AA.LT.TOL/AZ) GO TO 40
  158. TRM1 = CONE
  159. TRM2 = CONE
  160. ATRM = 1.0E0
  161. Z3 = Z*Z*Z
  162. AZ3 = AZ*AA
  163. AK = 2.0E0 + FID
  164. BK = 3.0E0 - FID - FID
  165. CK = 4.0E0 - FID
  166. DK = 3.0E0 + FID + FID
  167. D1 = AK*DK
  168. D2 = BK*CK
  169. AD = MIN(D1,D2)
  170. AK = 24.0E0 + 9.0E0*FID
  171. BK = 30.0E0 - 9.0E0*FID
  172. Z3R = REAL(Z3)
  173. Z3I = AIMAG(Z3)
  174. DO 30 K=1,25
  175. TRM1 = TRM1*CMPLX(Z3R/D1,Z3I/D1)
  176. S1 = S1 + TRM1
  177. TRM2 = TRM2*CMPLX(Z3R/D2,Z3I/D2)
  178. S2 = S2 + TRM2
  179. ATRM = ATRM*AZ3/AD
  180. D1 = D1 + AK
  181. D2 = D2 + BK
  182. AD = MIN(D1,D2)
  183. IF (ATRM.LT.TOL*AD) GO TO 40
  184. AK = AK + 18.0E0
  185. BK = BK + 18.0E0
  186. 30 CONTINUE
  187. 40 CONTINUE
  188. IF (ID.EQ.1) GO TO 50
  189. BI = S1*CMPLX(C1,0.0E0) + Z*S2*CMPLX(C2,0.0E0)
  190. IF (KODE.EQ.1) RETURN
  191. ZTA = Z*CSQRT(Z)*CMPLX(TTH,0.0E0)
  192. AA = REAL(ZTA)
  193. AA = -ABS(AA)
  194. BI = BI*CMPLX(EXP(AA),0.0E0)
  195. RETURN
  196. 50 CONTINUE
  197. BI = S2*CMPLX(C2,0.0E0)
  198. IF (AZ.GT.TOL) BI = BI + Z*Z*S1*CMPLX(C1/(1.0E0+FID),0.0E0)
  199. IF (KODE.EQ.1) RETURN
  200. ZTA = Z*CSQRT(Z)*CMPLX(TTH,0.0E0)
  201. AA = REAL(ZTA)
  202. AA = -ABS(AA)
  203. BI = BI*CMPLX(EXP(AA),0.0E0)
  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 FNUL IS THE LOWER BOUNDARY OF THE ASYMPTOTIC SERIES FOR LARGE FNU.
  220. C-----------------------------------------------------------------------
  221. K1 = I1MACH(12)
  222. K2 = I1MACH(13)
  223. R1M5 = R1MACH(5)
  224. K = MIN(ABS(K1),ABS(K2))
  225. ELIM = 2.303E0*(K*R1M5-3.0E0)
  226. K1 = I1MACH(11) - 1
  227. AA = R1M5*K1
  228. DIG = MIN(AA,18.0E0)
  229. AA = AA*2.303E0
  230. ALIM = ELIM + MAX(-AA,-41.45E0)
  231. RL = 1.2E0*DIG + 3.0E0
  232. FNUL = 10.0E0 + 6.0E0*(DIG-3.0E0)
  233. C-----------------------------------------------------------------------
  234. C TEST FOR RANGE
  235. C-----------------------------------------------------------------------
  236. AA=0.5E0/TOL
  237. BB=I1MACH(9)*0.5E0
  238. AA=MIN(AA,BB)
  239. AA=AA**TTH
  240. IF (AZ.GT.AA) GO TO 190
  241. AA=SQRT(AA)
  242. IF (AZ.GT.AA) IERR=3
  243. CSQ=CSQRT(Z)
  244. ZTA=Z*CSQ*CMPLX(TTH,0.0E0)
  245. C-----------------------------------------------------------------------
  246. C RE(ZTA).LE.0 WHEN RE(Z).LT.0, ESPECIALLY WHEN IM(Z) IS SMALL
  247. C-----------------------------------------------------------------------
  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.EQ.0.0E0 .AND. ZR.LE.0.0E0) ZTA = CMPLX(0.0E0,AK)
  258. AA = REAL(ZTA)
  259. IF (KODE.EQ.2) GO TO 80
  260. C-----------------------------------------------------------------------
  261. C OVERFLOW TEST
  262. C-----------------------------------------------------------------------
  263. BB = ABS(AA)
  264. IF (BB.LT.ALIM) GO TO 80
  265. BB = BB + 0.25E0*ALOG(AZ)
  266. SFAC = TOL
  267. IF (BB.GT.ELIM) GO TO 170
  268. 80 CONTINUE
  269. FMR = 0.0E0
  270. IF (AA.GE.0.0E0 .AND. ZR.GT.0.0E0) GO TO 90
  271. FMR = PI
  272. IF (ZI.LT.0.0E0) FMR = -PI
  273. ZTA = -ZTA
  274. 90 CONTINUE
  275. C-----------------------------------------------------------------------
  276. C AA=FACTOR FOR ANALYTIC CONTINUATION OF I(FNU,ZTA)
  277. C KODE=2 RETURNS EXP(-ABS(XZTA))*I(FNU,ZTA) FROM CBINU
  278. C-----------------------------------------------------------------------
  279. CALL CBINU(ZTA, FNU, KODE, 1, CY, NZ, RL, FNUL, TOL, ELIM, ALIM)
  280. IF (NZ.LT.0) GO TO 180
  281. AA = FMR*FNU
  282. Z3 = CMPLX(SFAC,0.0E0)
  283. S1 = CY(1)*CMPLX(COS(AA),SIN(AA))*Z3
  284. FNU = (2.0E0-FID)/3.0E0
  285. CALL CBINU(ZTA, FNU, KODE, 2, CY, NZ, RL, FNUL, TOL, ELIM, ALIM)
  286. CY(1) = CY(1)*Z3
  287. CY(2) = CY(2)*Z3
  288. C-----------------------------------------------------------------------
  289. C BACKWARD RECUR ONE STEP FOR ORDERS -1/3 OR -2/3
  290. C-----------------------------------------------------------------------
  291. S2 = CY(1)*CMPLX(FNU+FNU,0.0E0)/ZTA + CY(2)
  292. AA = FMR*(FNU-1.0E0)
  293. S1 = (S1+S2*CMPLX(COS(AA),SIN(AA)))*CMPLX(COEF,0.0E0)
  294. IF (ID.EQ.1) GO TO 100
  295. S1 = CSQ*S1
  296. BI = S1*CMPLX(1.0E0/SFAC,0.0E0)
  297. RETURN
  298. 100 CONTINUE
  299. S1 = Z*S1
  300. BI = S1*CMPLX(1.0E0/SFAC,0.0E0)
  301. RETURN
  302. 110 CONTINUE
  303. AA = C1*(1.0E0-FID) + FID*C2
  304. BI = CMPLX(AA,0.0E0)
  305. RETURN
  306. 170 CONTINUE
  307. NZ=0
  308. IERR=2
  309. RETURN
  310. 180 CONTINUE
  311. IF(NZ.EQ.(-1)) GO TO 170
  312. NZ=0
  313. IERR=5
  314. RETURN
  315. 190 CONTINUE
  316. IERR=4
  317. NZ=0
  318. RETURN
  319. END