{- Copyright (C) 2011 Dr. Alistair Ward This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | [@AUTHOR@] Dr. Alistair Ward [@DESCRIPTION@] Miscellaneous statistical functions. -} module Factory.Math.Statistics( -- * Functions getMean, -- getDispersionFromMean, getVariance, getStandardDeviation, getAverageAbsoluteDeviation, getCoefficientOfVariance, nCr, nPr ) where import Control.Arrow((***)) import Control.Parallel(par, pseq) import qualified Data.List import qualified Data.Ratio import qualified Factory.Math.Factorial as Math.Factorial import qualified Factory.Math.Implementations.Factorial as Math.Implementations.Factorial import qualified Factory.Math.Power as Math.Power {- | * Determines the /mean/ of the specified list of numbers; . * Should the caller define the result-type as 'Data.Ratio.Rational', then it will be free from rounding-errors. -} getMean :: (Real r, Fractional result) => [r] -> result getMean [] = error "Factory.Math.Statistics.getMean:\tundefined result for null-list." getMean [x] = realToFrac x --Not necessary, but a shortcut for this special case. getMean l = uncurry (/) . (realToFrac *** fromIntegral) $ foldr (\s -> (+ s) *** succ) (0, 0 :: Int) l {- | * Measures the dispersion of a population of results from the mean value; . * Should the caller define the result-type as 'Data.Ratio.Rational', then it will be free from rounding-errors. -} getDispersionFromMean :: (Real r, Fractional result) => (Data.Ratio.Rational -> Data.Ratio.Rational) -> [r] -> result getDispersionFromMean _ [] = error "Factory.Math.Statistics.getDispersionFromMean:\tundefined result for null-list." getDispersionFromMean _ [_] = 0 --Not necessary, but a shortcut for this special case. getDispersionFromMean measure l = getMean $ map (measure . (+ negate (getMean l :: Data.Ratio.Rational)) . realToFrac) l {- | * Determines the exact /variance/ of the specified list of numbers; . * Should the caller define the result-type as 'Data.Ratio.Rational', then it will be free from rounding-errors. -} getVariance :: (Real r, Fractional result) => [r] -> result getVariance = getDispersionFromMean Math.Power.square -- | Determines the /standard-deviation/ of the specified list of numbers; . getStandardDeviation :: (Real r, Floating result) => [r] -> result getStandardDeviation = sqrt . getVariance {- | * Determines the /average absolute deviation/ of the specified list of numbers; . * Should the caller define the result-type as 'Data.Ratio.Rational', then it will be free from rounding-errors. -} getAverageAbsoluteDeviation :: (Real r, Fractional result) => [r] -> result getAverageAbsoluteDeviation = getDispersionFromMean abs -- | Determines the /coefficient-of-variance/ of the specified list of numbers; . getCoefficientOfVariance :: (Real r, Floating result) => [r] -> result getCoefficientOfVariance l | mean == 0 = error "Factory.Math.Statistics.getCoefficientOfVariance:\tundefined if mean is zero." | otherwise = getStandardDeviation l / abs mean where mean = getMean l -- | The number of unordered combinations of /r/ objects taken from /n/; . nCr :: (Math.Factorial.Algorithm factorialAlgorithm, Integral i) => factorialAlgorithm -> i -- ^ The total number of items from which to select. -> i -- ^ The number of items in a sample. -> i -- ^ The number of combinations. nCr _ 0 _ = 1 nCr _ _ 0 = 1 nCr factorialAlgorithm n r | n < 0 = error $ "Factory.Math.Statistics.nCr:\tinvalid n; " ++ show n | r < 0 = error $ "Factory.Math.Statistics.nCr:\tinvalid r; " ++ show r | n < r = 0 | otherwise = numerator `par` (denominator `pseq` numerator `div` denominator) where [smaller, bigger] = Data.List.sort [r, n - r] numerator = Math.Implementations.Factorial.risingFactorial (bigger + 1) (n - bigger) denominator = Math.Factorial.factorial factorialAlgorithm smaller -- | The number of permutations of /r/ objects taken from /n/; . nPr :: Integral i => i -- ^ The total number of items from which to select. -> i -- ^ The number of items in a sample. -> i -- ^ The number of permutations. nPr 0 _ = 1 nPr _ 0 = 1 nPr n r | n < 0 = error $ "Factory.Math.Statistics.nPr:\tinvalid n; " ++ show n | r < 0 = error $ "Factory.Math.Statistics.nPr:\tinvalid r; " ++ show r | n < r = 0 | otherwise = Math.Implementations.Factorial.fallingFactorial n r