module Math.SphericalHarmonics.AssociatedLegendre
(
associatedLegendreFunction
, schmidtSemiNormalizedAssociatedLegendreFunction
)
where
import Data.Poly (VPoly, eval, deriv)
import Data.Poly.Orthogonal (legendre)
import Data.Euclidean (Field, WrappedFractional(..))
associatedLegendreFunction :: (Floating a, Ord a) => Int
-> Int
-> a -> a
associatedLegendreFunction n m = f
where
f x = nonPolyTerm x * unwrapFractional (eval p' (WrapFractional x))
nonPolyTerm x = (1 - x * x) ** (fromIntegral m / 2)
p' = iterate deriv p !! m
p :: (Eq t, Field t) => VPoly t
p = legendre !! n
schmidtSemiNormalizedAssociatedLegendreFunction :: (Floating a, Ord a) => Int
-> Int
-> a -> a
schmidtSemiNormalizedAssociatedLegendreFunction n 0 = associatedLegendreFunction n 0
schmidtSemiNormalizedAssociatedLegendreFunction n m = (* factor) . associatedLegendreFunction n m
where
factor = (sqrt $ 2 / rawFactor)
rawFactor = fromIntegral $ rawFactor' (fromIntegral n) (fromIntegral m)
rawFactor' :: Integer -> Integer -> Integer
rawFactor' n m = product . map (max 1) $ enumFromTo (n - m + 1) (n + m)