Skip to content

Commit

Permalink
Cleaned up Haddocks and function signatures to fix doc errors.
Browse files Browse the repository at this point in the history
  • Loading branch information
lukehoersten committed Mar 26, 2012
1 parent f38b9c4 commit 62e32cd
Showing 1 changed file with 34 additions and 31 deletions.
65 changes: 34 additions & 31 deletions src/Math/Statistics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,72 +18,73 @@ module Math.Statistics where
import Data.List
import Data.Ord (comparing)

-- |Numerically stable mean
-- | Numerically stable mean
mean :: Floating a => [a] -> a
mean x = fst $ foldl' (\(!m, !n) x -> (m+(x-m)/(n+1),n+1)) (0,0) x

-- |Same as 'mean'
-- | Same as 'mean'
average :: Floating a => [a] -> a
average = mean

-- |Harmonic mean
-- | Harmonic mean
harmean :: (Floating a) => [a] -> a
harmean xs = fromIntegral (length xs) / (sum $ map (1/) xs)

-- |Geometric mean
-- | Geometric mean
geomean :: (Floating a) => [a] -> a
geomean xs = (foldr1 (*) xs)**(1 / fromIntegral (length xs))

-- |Median
-- | Median
median :: (Floating a, Ord a) => [a] -> a
median x | odd n = head $ drop (n `div` 2) x'
| even n = mean $ take 2 $ drop i x'
where i = (length x' `div` 2) - 1
x' = sort x
n = length x

-- |Modes returns a sorted list of modes in descending order
-- | Modes returns a sorted list of modes in descending order
modes :: (Ord a) => [a] -> [(Int, a)]
modes xs = sortBy (comparing $ negate.fst) $ map (\x->(length x, head x)) $ (group.sort) xs

-- |Mode returns the mode of the list, otherwise Nothing
-- | Mode returns the mode of the list, otherwise Nothing
mode :: (Ord a) => [a] -> Maybe a
mode xs = case m of
[] -> Nothing
otherwise -> Just . snd $ head m
where m = filter (\(a,b) -> a > 1) (modes xs)

-- |Central moments
-- | Central moments
centralMoment :: (Floating b, Integral t) => [b] -> t -> b
centralMoment xs 1 = 0
centralMoment xs r = (sum (map (\x -> (x-m)^r) xs)) / n
where
m = mean xs
n = fromIntegral $ length xs

-- |Range
-- | Range
range :: (Num a, Ord a) => [a] -> a
range xs = maximum xs - minimum xs

-- |Average deviation
-- | Average deviation
avgdev :: (Floating a) => [a] -> a
avgdev xs = mean $ map (\x -> abs(x - m)) xs
where
m = mean xs

-- |Standard deviation of sample
-- | Standard deviation of sample
stddev :: (Floating a) => [a] -> a
stddev xs = sqrt $ var xs

-- |Standard deviation of population
-- | Standard deviation of population
stddevp :: (Floating a) => [a] -> a
stddevp xs = sqrt $ pvar xs

-- |Population variance
-- | Population variance
pvar :: (Floating a) => [a] -> a
pvar xs = centralMoment xs 2

-- |Sample variance
-- | Sample variance
var :: Fractional a => [a] -> a
var xs = (var' 0 0 0 xs) / (fromIntegral $ length xs - 1)
where
var' _ _ s [] = s
Expand All @@ -92,21 +93,23 @@ var xs = (var' 0 0 0 xs) / (fromIntegral $ length xs - 1)
delta = x - m
nm = m + delta/(fromIntegral $ n + 1)

-- |Interquartile range
-- | Interquartile range
iqr :: [a] -> [a]
iqr xs = take (length xs - 2*q) $ drop q xs
where
q = ((length xs) + 1) `div` 4

-- Kurtosis
-- | Kurtosis
kurt :: Floating a => [a] -> a
kurt xs = ((centralMoment xs 4) / (centralMoment xs 2)^2)-3

-- |Arbitrary quantile q of an unsorted list. The quantile /q/ of /N/
-- |data points is the point whose (zero-based) index in the sorted
-- |data set is closest to /q(N-1)/.
-- | Arbitrary quantile q of an unsorted list. The quantile /q/ of /N/
-- data points is the point whose (zero-based) index in the sorted
-- data set is closest to /q(N-1)/.
quantile :: (Fractional b, Ord b) => Double -> [b] -> b
quantile q = quantileAsc q . sort

-- |As 'quantile' specialized for sorted data
-- | As 'quantile' specialized for sorted data
quantileAsc :: (Fractional b, Ord b) => Double -> [b] -> b
quantileAsc _ [] = error "quantile on empty list"
quantileAsc q xs
Expand All @@ -118,11 +121,11 @@ quantileAsc q xs
| idx >= len -> error "Quantile index too large"
| otherwise -> idx

-- |Calculate skew
-- | Calculate skew
skew :: (Floating b) => [b] -> b
skew xs = (centralMoment xs 3) / (centralMoment xs 2)**(3/2)

-- |Calculates pearson skew
-- | Calculates pearson skew
pearsonSkew1 :: (Ord a, Floating a) => [a] -> a
pearsonSkew1 xs = 3 * (mean xs - mo) / stddev xs
where
Expand All @@ -131,7 +134,7 @@ pearsonSkew1 xs = 3 * (mean xs - mo) / stddev xs
pearsonSkew2 :: (Ord a, Floating a) => [a] -> a
pearsonSkew2 xs = 3 * (mean xs - median xs) / stddev xs

-- |Sample Covariance
-- | Sample Covariance
covar :: (Floating a) => [a] -> [a] -> a
covar xs ys = sum (zipWith (*) (map f1 xs) (map f2 ys)) / (n-1)
where
Expand All @@ -141,25 +144,25 @@ covar xs ys = sum (zipWith (*) (map f1 xs) (map f2 ys)) / (n-1)
f1 = \x -> (x - m1)
f2 = \x -> (x - m2)

-- |Covariance matrix
-- | Covariance matrix
covMatrix :: (Floating a) => [[a]] -> [[a]]
covMatrix xs = split' (length xs) cs
where
cs = [ covar a b | a <- xs, b <- xs]
split' n = unfoldr (\y -> if null y then Nothing else Just $ splitAt n y)

-- |Pearson's product-moment correlation coefficient
-- | Pearson's product-moment correlation coefficient
pearson :: (Floating a) => [a] -> [a] -> a
pearson x y = covar x y / (stddev x * stddev y)

-- |Same as 'pearson'
-- | Same as 'pearson'
correl :: (Floating a) => [a] -> [a] -> a
correl = pearson

-- |Least-squares linear regression of /y/ against /x/ for a
-- |collection of (/x/, /y/) data, in the form of (/b0/, /b1/, /r/)
-- |where the regression is /y/ = /b0/ + /b1/ * /x/ with Pearson
-- |coefficient /r/
-- | Least-squares linear regression of /y/ against /x/ for a
-- collection of (/x/, /y/) data, in the form of (/b0/, /b1/, /r/)
-- where the regression is /y/ = /b0/ + /b1/ * /x/ with Pearson
-- coefficient /r/
linreg :: (Floating b) => [(b, b)] -> (b, b, b)
linreg xys = let !xs = map fst xys
!ys = map snd xys
Expand All @@ -175,7 +178,7 @@ linreg xys = let !xs = map fst xys
in (alpha, beta, r)


-- |Returns the sum of square deviations from their sample mean.
-- | Returns the sum of square deviations from their sample mean.
devsq :: (Floating a) => [a] -> a
devsq xs = sum $ map (\x->(x-m)**2) xs
where m = mean xs

0 comments on commit 62e32cd

Please sign in to comment.