{- |
This library provides tools for doing single parameter Bayesian inference.


Example ghci use:

> # Generate a discrete simulation of the uniform prior for the bias
> # of a single coin on [0,1] using a grid of 100 points.
> let prior = uniformPrior 100
> # Update the prior as if we flipped the coin 100 times and got 25 heads.
> let posterior = coins prior 25 75
> # Optionally, import Graphics.Gnuplot.Simple and convert posterior 
> # to a list of tuples for plotting using listify
> :m + Graphics.Gnuplot.Simple
> plotList [] (listify posterior)
> # As you'd expect, nearly all of the probability mass is concentrated
> # between a bias of 0.2 and 0.3
-}

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

{- |
Takes a list of elements and generates a uniform Distro over them.
-}
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)

{- |
Generates a simulated uniform distro over [0,1] with user supplied granularity. 
-}
uniformPrior :: Integer -> Distro Prob
uniformPrior granularity = uniformPDF xs
  where xs = map ( % granularity) [0..granularity]


{- |
Updates a distro with a new trial that either succeeded or failed. 
-}
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

{- |
Updates a distro with many trials, all of which either succeeded or failed.
-}
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)

{- |
Convert a Distro to a list of tuples for easier plotting.
-}
listify :: Distro k -> [(k, Prob)]
listify = Map.toList . runDistro