module Data.Summary.Bool (
Summary,
summary,
update,
sampleSize,
count,
sampleMean,
sampleSE,
sampleCI,
) where
import Control.DeepSeq
import Data.List( foldl' )
import Data.Monoid
import Text.Printf
import Data.Summary.Utils
data Summary = S !Int
!Int
instance Show Summary where
show s@(S n c) =
printf " sample size: %d" n
++ printf "\n successes: %d" c
++ printf "\n proportion: %g" (sampleMean s)
++ printf "\n SE: %g" (sampleSE s)
++ printf "\n 99%% CI: (%g, %g)" c1 c2
where (c1,c2) = sampleCI 0.99 s
instance Monoid Summary where
mempty = empty
mappend = union
instance NFData Summary
summary :: [Bool] -> Summary
summary = foldl' update empty
empty :: Summary
empty = S 0 0
union :: Summary -> Summary -> Summary
union (S na ca) (S nb cb) = S (na + nb) (ca + cb)
update :: Summary -> Bool -> Summary
update (S n c) i =
let n' = n+1
c' = if i then c+1 else c
in S n' c'
sampleSize :: Summary -> Int
sampleSize (S n _) = n
count :: Summary -> Int
count (S _ c) = c
sampleMean :: Summary -> Double
sampleMean (S n c) = fromIntegral c / fromIntegral n
sampleSE :: Summary -> Double
sampleSE s = sqrt (p*(1p) / n)
where p = sampleMean s
n = fromIntegral $ sampleSize s
sampleCI :: Double -> Summary -> (Double,Double)
sampleCI level s = interval level (sampleMean s) (sampleSE s)