{-# LANGUAGE DefaultSignatures #-} module Stochastic.Distribution(ContinuousDistribution(..), DiscreteDistribution(..)) where import Helpers(histogram, statefully) class DiscreteDistribution g where randInt :: g -> (Int, g) randInt g = randIntIn (0, maxBound::Int) g randInts :: Int -> g -> ([Int], g) randInts n g0 = statefully (randInt) n g0 randIntIn :: (Int, Int) -> g -> (Int, g) default randIntIn :: (ContinuousDistribution g) => (Int, Int) -> g -> (Int, g) randIntIn (a, b) g0 = ((ceiling (toDbl (b - a + 1) * d)) + (a-1), g1) where (d, g1) = randDouble g0 class ContinuousDistribution g where randDouble :: g -> (Double, g) randDoubles :: Int -> g -> ([Double], g) randDoubles n g0 = statefully (randDouble) n g0 toDbl = fromInteger . toInteger