module Data.Summary.Double (
Summary,
summary,
update,
sampleSize,
sampleMin,
sampleMax,
sampleMean,
sampleSE,
sampleVar,
sampleSD,
sampleCI,
) where
import Control.DeepSeq
import Data.List( foldl' )
import Data.Monoid
import Text.Printf
import Data.Summary.Utils
data Summary = S !Int
!Double
!Double
!Double
!Double
instance Show Summary where
show s@(S n mu _ l h) =
printf " sample size: %d" n
++ printf "\n min: %g" l
++ printf "\n max: %g" h
++ printf "\n mean: %g" mu
++ 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 :: [Double] -> Summary
summary = foldl' update empty
empty :: Summary
empty = S 0 0 0 (1/0) (1/0)
update :: Summary -> Double -> Summary
update (S n m s l h) x =
let n' = n+1
delta = x m
m' = m + delta / fromIntegral n'
s' = s + delta*(x m')
l' = if x < l then x else l
h' = if x > h then x else h
in S n' m' s' l' h'
union :: Summary -> Summary -> Summary
union (S na ma sa la ha) (S nb mb sb lb hb) =
let delta = mb ma
(na', nb') = (fromIntegral na, fromIntegral nb)
n = na + nb
n' = fromIntegral n
weightedDelta = delta*nb'/n'
m | n == 0 = 0
| otherwise = ma + weightedDelta
s | n == 0 = 0
| otherwise = sa + sb + delta*na'*weightedDelta
l = min la lb
h = max ha hb
in S n m s l h
sampleSize :: Summary -> Int
sampleSize (S n _ _ _ _) = n
sampleMean :: Summary -> Double
sampleMean (S _ m _ _ _) = m
sampleVar :: Summary -> Double
sampleVar (S n _ s _ _) = s / fromIntegral (n 1)
sampleSD :: Summary -> Double
sampleSD s = sqrt (sampleVar s)
sampleSE :: Summary -> Double
sampleSE s = sqrt (sampleVar s / fromIntegral (sampleSize s))
sampleCI :: Double -> Summary -> (Double,Double)
sampleCI level s = interval level (sampleMean s) (sampleSE s)
sampleMin :: Summary -> Double
sampleMin (S _ _ _ l _) = l
sampleMax :: Summary -> Double
sampleMax (S _ _ _ _ h) = h