commit beeb0d0bb77da493152e18f8c1e500b61d186ad5
parent 952dc91af3fa62c50b9d3ca1379d5b3727c0e2f5
Author: Jared Tobin <jared@jtobin.ca>
Date: Sat, 19 Oct 2013 21:35:52 +1300
Change 'mean' to 'expectation' everywhere.
Diffstat:
2 files changed, 15 insertions(+), 12 deletions(-)
diff --git a/src/Measurable.hs b/src/Measurable.hs
@@ -78,13 +78,13 @@ instance Monad Measure where
volume :: Measure a -> Double
volume mu = measure mu (const 1)
--- | The mean is obtained by integrating against the identity function.
-mean :: Measure Double -> Double
-mean mu = measure mu id
+-- | The expectation is obtained by integrating against the identity function.
+expectation :: Measure Double -> Double
+expectation mu = measure mu id
-- | The variance is obtained by integrating against the usual function.
variance :: Measure Double -> Double
-variance mu = measure mu (^ 2) - mean mu ^ 2
+variance mu = measure mu (^ 2) - expectation mu ^ 2
-- | Create a measure from a collection of observations from some distribution.
fromObservations :: Fractional a => [a] -> Measure a
@@ -103,7 +103,7 @@ identityMeasure = fromObservations []
average :: Fractional a => [a] -> a
average xs = fst $ foldl'
(\(!m, !n) x -> (m + (x - m) / fromIntegral (n + 1), n + 1)) (0, 0) xs
-{-# INLINE mean #-}
+{-# INLINE average #-}
-- | Weighted average.
weightedAverage :: Fractional c => (a -> c) -> [a] -> c
@@ -137,5 +137,5 @@ to a b x | x >= a && x <= b = 1
-- > cdf (1 / 0)
-- 0.999
cdf :: Measure Double -> Double -> Double
-cdf mu b = mean $ negate (1 / 0) `to` b <$> mu
+cdf mu b = expectation $ negate (1 / 0) `to` b <$> mu
diff --git a/tests/Test.hs b/tests/Test.hs
@@ -26,11 +26,11 @@ main = do
eta = exp <$> rho
putStrLn $ "mean of normal samples (should be around 0): " ++
- show (mean . fromObservations $ normSamples)
+ show (expectation . fromObservations $ normSamples)
putStrLn $ "variance of normal samples (should be around 1): " ++
show (variance . fromObservations $ normSamples)
putStrLn $ "let X ~ N(0, 1), Y ~ observed. mean of exp(cos X + sin Y): " ++
- show (mean eta)
+ show (expectation eta)
putStrLn ""
putStrLn "and now some 'woah, this actally seems to make sense' examples:"
@@ -41,7 +41,7 @@ main = do
let iota = mu - mu
putStrLn $ "let X, Y be independent N(0, 1). mean of X - Y: " ++
- show (mean iota)
+ show (expectation iota)
putStrLn $ "let X, Y be independent N(0, 1). variance of X - Y: " ++
show (variance iota)
@@ -52,7 +52,7 @@ main = do
zeta = phi * xi
putStrLn $ "let X ~ N(2, 1), Y ~ N(3, 1). mean of XY (should be 6) " ++
- show (mean zeta)
+ show (expectation zeta)
putStrLn $ "let X ~ N(2, 1), Y ~ N(3, 1). variance of XY (should be 14) " ++
show (variance zeta)
@@ -67,9 +67,12 @@ main = do
putStrLn ""
putStrLn $ "let X ~ N(0, 1). P(X < 0) (should be ~ 0.5): " ++
- show (mean $ negate (1 / 0) `to` 0 <$> mu)
+ show (cdf mu 0)
putStrLn $ "let X ~ N(0, 1). P(0 < X < 1) (should be ~ 0.341): " ++
- show (mean $ 0 `to` 1 <$> mu)
+ show (expectation $ 0 `to` 1 <$> mu)
+
+ putStrLn $ "let X ~ N(0, 1), Y ~ observed. P(0 < X < 0.8): " ++
+ show (expectation $ 0 `to` 0.8 <$> (mu + nu))