{-# LANGUAGE BangPatterns #-} import Data.Array.Vector import Math.Statistics.Fusion import Data.List import Test.QuickCheck ------------------------------------------------------------------------ prop_mean ds = mean (toU ds) == model_mean ds where model_mean :: Floating a => [a] -> a model_mean x = fst $ foldl' (\(!m, !n) x -> (m+(x-m)/(n+1),n+1)) (0,0) x ------------------------------------------------------------------------ prop_harmonic ds = not (null ds) ==> harmonic (toU ds) == model_harmonic ds where model_harmonic :: (Floating a) => [a] -> a model_harmonic xs = fromIntegral (length xs) / (sum $ map (1/) xs) ------------------------------------------------------------------------ prop_geometric ds = not (null ds) ==> geometric (toU ds) == model_geometric ds where model_geometric :: (Floating a) => [a] -> a model_geometric xs = (foldr1 (*) xs)**(1 / fromIntegral (length xs))