module Numeric.Learn where import Data.Ratio import qualified Data.Map as Map type Prob = Ratio Integer newtype Distro a = Distro { runDistro :: Map.Map a Prob } deriving (Eq,Ord,Read,Show) data Result = Positive | Negative uniformPDF :: (Ord k) => [k] -> Distro k uniformPDF xs = Distro $ foldl (\thisMap elt -> Map.insert elt (1 % len) thisMap) Map.empty xs where len = fromIntegral (length xs) --Want single parameter Bayesian estimation --we take a (Distro Prob) and transform it --P(Hi|Ej) = (P(Ej|Hi) / P(Ej))* P(Hi) uniformPrior :: Integer -> Distro Prob uniformPrior granularity = uniformPDF xs where xs = map ( % granularity) [0..granularity] singleCoin :: Distro Prob -> Result -> Distro Prob singleCoin (Distro probs) result = Distro $ Map.mapWithKey (update result) probs where update Positive = \pE1gHi pHi -> (pE1gHi / pE1) * pHi update Negative = \pE1gHi pHi -> ((1 - pE1gHi) / (1 - pE1)) * pHi pE1 = Map.foldWithKey (\k a acc -> acc + k * a) 0 probs coins :: Distro Prob -> Int -> Int -> Distro Prob coins distro heads tails = foldl (\thisDistro result -> singleCoin thisDistro result) distro results where results = (take heads $ repeat Positive) ++ (take tails $ repeat Negative) listify :: Distro k -> [(k, Prob)] listify = Map.toList . runDistro