Skip to content

Commit

Permalink
Cleanups.
Browse files Browse the repository at this point in the history
  • Loading branch information
bos committed Sep 11, 2009
1 parent 5e0dca0 commit c0a5c42
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 18 deletions.
4 changes: 2 additions & 2 deletions Statistics/Constants.hs
Expand Up @@ -46,5 +46,5 @@ m_1_sqrt_2 = 0.7071067811865475244008443621048490392848359376884740365883

-- | The smallest 'Double' larger than 1.
m_epsilon :: Double
m_epsilon = encodeFloat (significand+1) exponent - 1.0
where (significand,exponent) = decodeFloat (1.0::Double)
m_epsilon = encodeFloat (signif+1) expo - 1.0
where (signif,expo) = decodeFloat (1.0::Double)
30 changes: 14 additions & 16 deletions Statistics/Sample.hs
Expand Up @@ -42,28 +42,29 @@ import Statistics.Types (Sample)
-- | Arithmetic mean. This uses Welford's algorithm to provide
-- numerical stability, using a single pass over the sample data.
mean :: Sample -> Double
mean = fstT . foldlU k (T 0 0)
where
k (T m n) x = T m' n'
where m' = m + (x - m) / fromIntegral n'
n' = n + 1
mean = fini . foldlU go (T 0 0)
where
fini (T a _) = a
go (T m n) x = T m' n'
where m' = m + (x - m) / fromIntegral n'
n' = n + 1
{-# INLINE mean #-}

-- | Harmonic mean. This algorithm performs a single pass over the
-- sample.
harmonicMean :: Sample -> Double
harmonicMean xs = fromIntegral a / b
harmonicMean = fini . foldlU go (T 0 0)
where
T b a = foldlU k (T 0 0) xs
k (T b a) n = T (b + (1/n)) (a+1)
fini (T b a) = fromIntegral a / b
go (T x y) n = T (x + (1/n)) (y+1)
{-# INLINE harmonicMean #-}

-- | Geometric mean of a sample containing no negative values.
geometricMean :: Sample -> Double
geometricMean xs = p ** (1 / fromIntegral n)
geometricMean = fini . foldlU go (T 1 0)
where
T p n = foldlU k (T 1 0) xs
k (T p n) a = T (p * a) (n + 1)
fini (T p n) = p ** (1 / fromIntegral n)
go (T p n) a = T (p * a) (n + 1)
{-# INLINE geometricMean #-}

-- $variance
Expand All @@ -81,15 +82,15 @@ geometricMean xs = p ** (1 / fromIntegral n)
-- subject to stream fusion.

robustVar :: Sample -> T
robustVar s = fini . foldlU go (T1 0 0 0) $ s
robustVar samp = fini . foldlU go (T1 0 0 0) $ samp
where
go (T1 n s c) x = T1 n' s' c'
where n' = n + 1
s' = s + d * d
c' = c + d
d = x - m
fini (T1 n s c) = T (s - c ** (2 / fromIntegral n)) n
m = mean s
m = mean samp

-- | Maximum likelihood estimate of a sample's variance.
variance :: Sample -> Double
Expand Down Expand Up @@ -162,9 +163,6 @@ data T = T {-# UNPACK #-}!Double {-# UNPACK #-}!Int

data T1 = T1 {-# UNPACK #-}!Int {-# UNPACK #-}!Double {-# UNPACK #-}!Double

fstT :: T -> Double
fstT (T a _) = a

{-
Consider this core:
Expand Down

0 comments on commit c0a5c42

Please sign in to comment.