dxnrmp.f 9.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269
  1. *DECK DXNRMP
  2. SUBROUTINE DXNRMP (NU, MU1, MU2, DARG, MODE, DPN, IPN, ISIG,
  3. 1 IERROR)
  4. C***BEGIN PROLOGUE DXNRMP
  5. C***PURPOSE Compute normalized Legendre polynomials.
  6. C***LIBRARY SLATEC
  7. C***CATEGORY C3A2, C9
  8. C***TYPE DOUBLE PRECISION (XNRMP-S, DXNRMP-D)
  9. C***KEYWORDS LEGENDRE FUNCTIONS
  10. C***AUTHOR Lozier, Daniel W., (National Bureau of Standards)
  11. C Smith, John M., (NBS and George Mason University)
  12. C***DESCRIPTION
  13. C
  14. C SUBROUTINE TO CALCULATE NORMALIZED LEGENDRE POLYNOMIALS
  15. C (XNRMP is single-precision version)
  16. C DXNRMP calculates normalized Legendre polynomials of varying
  17. C order and fixed argument and degree. The order MU and degree
  18. C NU are non-negative integers and the argument is real. Because
  19. C the algorithm requires the use of numbers outside the normal
  20. C machine range, this subroutine employs a special arithmetic
  21. C called extended-range arithmetic. See J.M. Smith, F.W.J. Olver,
  22. C and D.W. Lozier, Extended-Range Arithmetic and Normalized
  23. C Legendre Polynomials, ACM Transactions on Mathematical Soft-
  24. C ware, 93-105, March 1981, for a complete description of the
  25. C algorithm and special arithmetic. Also see program comments
  26. C in DXSET.
  27. C
  28. C The normalized Legendre polynomials are multiples of the
  29. C associated Legendre polynomials of the first kind where the
  30. C normalizing coefficients are chosen so as to make the integral
  31. C from -1 to 1 of the square of each function equal to 1. See
  32. C E. Jahnke, F. Emde and F. Losch, Tables of Higher Functions,
  33. C McGraw-Hill, New York, 1960, p. 121.
  34. C
  35. C The input values to DXNRMP are NU, MU1, MU2, DARG, and MODE.
  36. C These must satisfy
  37. C 1. NU .GE. 0 specifies the degree of the normalized Legendre
  38. C polynomial that is wanted.
  39. C 2. MU1 .GE. 0 specifies the lowest-order normalized Legendre
  40. C polynomial that is wanted.
  41. C 3. MU2 .GE. MU1 specifies the highest-order normalized Leg-
  42. C endre polynomial that is wanted.
  43. C 4a. MODE = 1 and -1.0D0 .LE. DARG .LE. 1.0D0 specifies that
  44. C Normalized Legendre(NU, MU, DARG) is wanted for MU = MU1,
  45. C MU1 + 1, ..., MU2.
  46. C 4b. MODE = 2 and -3.14159... .LT. DARG .LT. 3.14159... spec-
  47. C ifies that Normalized Legendre(NU, MU, COS(DARG)) is
  48. C wanted for MU = MU1, MU1 + 1, ..., MU2.
  49. C
  50. C The output of DXNRMP consists of the two vectors DPN and IPN
  51. C and the error estimate ISIG. The computed values are stored as
  52. C extended-range numbers such that
  53. C (DPN(1),IPN(1))=NORMALIZED LEGENDRE(NU,MU1,DX)
  54. C (DPN(2),IPN(2))=NORMALIZED LEGENDRE(NU,MU1+1,DX)
  55. C .
  56. C .
  57. C (DPN(K),IPN(K))=NORMALIZED LEGENDRE(NU,MU2,DX)
  58. C where K = MU2 - MU1 + 1 and DX = DARG or COS(DARG) according
  59. C to whether MODE = 1 or 2. Finally, ISIG is an estimate of the
  60. C number of decimal digits lost through rounding errors in the
  61. C computation. For example if DARG is accurate to 12 significant
  62. C decimals, then the computed function values are accurate to
  63. C 12 - ISIG significant decimals (except in neighborhoods of
  64. C zeros).
  65. C
  66. C The interpretation of (DPN(I),IPN(I)) is DPN(I)*(IR**IPN(I))
  67. C where IR is the internal radix of the computer arithmetic. When
  68. C IPN(I) = 0 the value of the normalized Legendre polynomial is
  69. C contained entirely in DPN(I) and subsequent double-precision
  70. C computations can be performed without further consideration of
  71. C extended-range arithmetic. However, if IPN(I) .NE. 0 the corre-
  72. C sponding value of the normalized Legendre polynomial cannot be
  73. C represented in double-precision because of overflow or under-
  74. C flow. THE USER MUST TEST IPN(I) IN HIS/HER PROGRAM. In the case
  75. C that IPN(I) is nonzero, the user could rewrite his/her program
  76. C to use extended range arithmetic.
  77. C
  78. C
  79. C
  80. C The interpretation of (DPN(I),IPN(I)) can be changed to
  81. C DPN(I)*(10**IPN(I)) by calling the extended-range subroutine
  82. C DXCON. This should be done before printing the computed values.
  83. C As an example of usage, the Fortran coding
  84. C J = K
  85. C DO 20 I = 1, K
  86. C CALL DXCON(DPN(I), IPN(I),IERROR)
  87. C IF (IERROR.NE.0) RETURN
  88. C PRINT 10, DPN(I), IPN(I)
  89. C 10 FORMAT(1X, D30.18 , I15)
  90. C IF ((IPN(I) .EQ. 0) .OR. (J .LT. K)) GO TO 20
  91. C J = I - 1
  92. C 20 CONTINUE
  93. C will print all computed values and determine the largest J
  94. C such that IPN(1) = IPN(2) = ... = IPN(J) = 0. Because of the
  95. C change of representation caused by calling DXCON, (DPN(I),
  96. C IPN(I)) for I = J+1, J+2, ... cannot be used in subsequent
  97. C extended-range computations.
  98. C
  99. C IERROR is an error indicator. If no errors are detected,
  100. C IERROR=0 when control returns to the calling routine. If
  101. C an error is detected, IERROR is returned as nonzero. The
  102. C calling routine must check the value of IERROR.
  103. C
  104. C If IERROR=212 or 213, invalid input was provided to DXNRMP.
  105. C If IERROR=201,202,203, or 204, invalid input was provided
  106. C to DXSET.
  107. C If IERROR=205 or 206, an internal consistency error occurred
  108. C in DXSET (probably due to a software malfunction in the
  109. C library routine I1MACH).
  110. C If IERROR=207, an overflow or underflow of an extended-range
  111. C number was detected in DXADJ.
  112. C If IERROR=208, an overflow or underflow of an extended-range
  113. C number was detected in DXC210.
  114. C
  115. C***SEE ALSO DXSET
  116. C***REFERENCES Smith, Olver and Lozier, Extended-Range Arithmetic and
  117. C Normalized Legendre Polynomials, ACM Trans on Math
  118. C Softw, v 7, n 1, March 1981, pp 93--105.
  119. C***ROUTINES CALLED DXADD, DXADJ, DXRED, DXSET, XERMSG
  120. C***REVISION HISTORY (YYMMDD)
  121. C 820712 DATE WRITTEN
  122. C 890126 Revised to meet SLATEC CML recommendations. (DWL and JMS)
  123. C 901019 Revisions to prologue. (DWL and WRB)
  124. C 901106 Changed all specific intrinsics to generic. (WRB)
  125. C Corrected order of sections in prologue and added TYPE
  126. C section. (WRB)
  127. C CALLs to XERROR changed to CALLs to XERMSG. (WRB)
  128. C 920127 Revised PURPOSE section of prologue. (DWL)
  129. C***END PROLOGUE DXNRMP
  130. INTEGER NU, MU1, MU2, MODE, IPN, ISIG
  131. DOUBLE PRECISION DARG, DPN
  132. DIMENSION DPN(*), IPN(*)
  133. DOUBLE PRECISION C1,C2,P,P1,P2,P3,S,SX,T,TX,X,DK
  134. C CALL DXSET TO INITIALIZE EXTENDED-RANGE ARITHMETIC (SEE DXSET
  135. C LISTING FOR DETAILS)
  136. C***FIRST EXECUTABLE STATEMENT DXNRMP
  137. IERROR=0
  138. CALL DXSET (0, 0, 0.0D0, 0,IERROR)
  139. IF (IERROR.NE.0) RETURN
  140. C
  141. C TEST FOR PROPER INPUT VALUES.
  142. C
  143. IF (NU.LT.0) GO TO 110
  144. IF (MU1.LT.0) GO TO 110
  145. IF (MU1.GT.MU2) GO TO 110
  146. IF (NU.EQ.0) GO TO 90
  147. IF (MODE.LT.1 .OR. MODE.GT.2) GO TO 110
  148. GO TO (10, 20), MODE
  149. 10 IF (ABS(DARG).GT.1.0D0) GO TO 120
  150. IF (ABS(DARG).EQ.1.0D0) GO TO 90
  151. X = DARG
  152. SX = SQRT((1.0D0+ABS(X))*((0.5D0-ABS(X))+0.5D0))
  153. TX = X/SX
  154. ISIG = LOG10(2.0D0*NU*(5.0D0+TX**2))
  155. GO TO 30
  156. 20 IF (ABS(DARG).GT.4.0D0*ATAN(1.0D0)) GO TO 120
  157. IF (DARG.EQ.0.0D0) GO TO 90
  158. X = COS(DARG)
  159. SX = ABS(SIN(DARG))
  160. TX = X/SX
  161. ISIG = LOG10(2.0D0*NU*(5.0D0+ABS(DARG*TX)))
  162. C
  163. C BEGIN CALCULATION
  164. C
  165. 30 MU = MU2
  166. I = MU2 - MU1 + 1
  167. C
  168. C IF MU.GT.NU, NORMALIZED LEGENDRE(NU,MU,X)=0.
  169. C
  170. 40 IF (MU.LE.NU) GO TO 50
  171. DPN(I) = 0.0D0
  172. IPN(I) = 0
  173. I = I - 1
  174. MU = MU - 1
  175. IF (I .GT. 0) GO TO 40
  176. ISIG = 0
  177. GO TO 160
  178. 50 MU = NU
  179. C
  180. C P1 = 0. = NORMALIZED LEGENDRE(NU,NU+1,X)
  181. C
  182. P1 = 0.0D0
  183. IP1 = 0
  184. C
  185. C CALCULATE P2 = NORMALIZED LEGENDRE(NU,NU,X)
  186. C
  187. P2 = 1.0D0
  188. IP2 = 0
  189. P3 = 0.5D0
  190. DK = 2.0D0
  191. DO 60 J=1,NU
  192. P3 = ((DK+1.0D0)/DK)*P3
  193. P2 = P2*SX
  194. CALL DXADJ(P2, IP2,IERROR)
  195. IF (IERROR.NE.0) RETURN
  196. DK = DK + 2.0D0
  197. 60 CONTINUE
  198. P2 = P2*SQRT(P3)
  199. CALL DXADJ(P2, IP2,IERROR)
  200. IF (IERROR.NE.0) RETURN
  201. S = 2.0D0*TX
  202. T = 1.0D0/NU
  203. IF (MU2.LT.NU) GO TO 70
  204. DPN(I) = P2
  205. IPN(I) = IP2
  206. I = I - 1
  207. IF (I .EQ. 0) GO TO 140
  208. C
  209. C RECURRENCE PROCESS
  210. C
  211. 70 P = MU*T
  212. C1 = 1.0D0/SQRT((1.0D0-P+T)*(1.0D0+P))
  213. C2 = S*P*C1*P2
  214. C1 = -SQRT((1.0D0+P+T)*(1.0D0-P))*C1*P1
  215. CALL DXADD(C2, IP2, C1, IP1, P, IP,IERROR)
  216. IF (IERROR.NE.0) RETURN
  217. MU = MU - 1
  218. IF (MU.GT.MU2) GO TO 80
  219. C
  220. C STORE IN ARRAY DPN FOR RETURN TO CALLING ROUTINE.
  221. C
  222. DPN(I) = P
  223. IPN(I) = IP
  224. I = I - 1
  225. IF (I .EQ. 0) GO TO 140
  226. 80 P1 = P2
  227. IP1 = IP2
  228. P2 = P
  229. IP2 = IP
  230. IF (MU.LE.MU1) GO TO 140
  231. GO TO 70
  232. C
  233. C SPECIAL CASE WHEN X=-1 OR +1, OR NU=0.
  234. C
  235. 90 K = MU2 - MU1 + 1
  236. DO 100 I=1,K
  237. DPN(I) = 0.0D0
  238. IPN(I) = 0
  239. 100 CONTINUE
  240. ISIG = 0
  241. IF (MU1.GT.0) GO TO 160
  242. ISIG = 1
  243. DPN(1) = SQRT(NU+0.5D0)
  244. IPN(1) = 0
  245. IF (MOD(NU,2).EQ.0) GO TO 160
  246. IF (MODE.EQ.1 .AND. DARG.EQ.1.0D0) GO TO 160
  247. IF (MODE.EQ.2) GO TO 160
  248. DPN(1) = -DPN(1)
  249. GO TO 160
  250. C
  251. C ERROR PRINTOUTS AND TERMINATION.
  252. C
  253. 110 CALL XERMSG ('SLATEC', 'DXNRMP', 'NU, MU1, MU2 or MODE not valid',
  254. + 212, 1)
  255. IERROR=212
  256. RETURN
  257. 120 CALL XERMSG ('SLATEC', 'DXNRMP', 'DARG out of range', 213, 1)
  258. IERROR=213
  259. RETURN
  260. C
  261. C RETURN TO CALLING PROGRAM
  262. C
  263. 140 K = MU2 - MU1 + 1
  264. DO 150 I=1,K
  265. CALL DXRED(DPN(I),IPN(I),IERROR)
  266. IF (IERROR.NE.0) RETURN
  267. 150 CONTINUE
  268. 160 RETURN
  269. END