module Factory.Math.Statistics(
getMean,
getRootMeanSquare,
getWeightedMean,
getVariance,
getStandardDeviation,
getAverageAbsoluteDeviation,
getCoefficientOfVariance,
nCr,
nPr
) where
import Control.Arrow((***))
import qualified Control.Exception
import Control.Parallel(par, pseq)
import qualified Data.Foldable
import qualified Data.List
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
getMean :: (
Data.Foldable.Foldable foldable,
Fractional result,
Real value
)
=> foldable value
-> result
getMean foldable = Control.Exception.assert (denominator /= 0) $ realToFrac numerator / fromIntegral denominator where
denominator :: Int
(numerator, denominator) = Data.Foldable.foldl' (
\acc x -> let
acc'@(n, d) = (+ x) *** succ $ acc
in n `seq` d `seq` acc'
) (0, 0) foldable
getRootMeanSquare :: (
Data.Foldable.Foldable foldable,
Floating result,
Real value
)
=> foldable value
-> result
getRootMeanSquare foldable = Control.Exception.assert (denominator /= 0) $ sqrt $ realToFrac numerator / fromIntegral denominator where
denominator :: Int
(numerator, denominator) = Data.Foldable.foldl' (
\acc x -> let
acc'@(n, d) = (+ Math.Power.square x) *** succ $ acc
in n `seq` d `seq` acc'
) (0, 0) foldable
getWeightedMean :: (
Data.Foldable.Foldable foldable,
Eq result,
Fractional result,
Real value,
Real weight
)
=> foldable (value, weight)
-> result
getWeightedMean foldable = Control.Exception.assert (denominator /= 0) $ numerator / denominator where
(numerator, denominator) = Data.Foldable.foldl' (
\acc (value, weight) -> case realToFrac weight of
0 -> acc
w -> let
acc'@(n, d) = (+ realToFrac value * w) *** (+ w) $ acc
in n `seq` d `seq` acc'
) (0, 0) foldable
getDispersionFromMean :: (
Data.Foldable.Foldable foldable,
Fractional result,
Functor foldable,
Real value
) => (Rational -> Rational) -> foldable value -> result
getDispersionFromMean weight foldable = getMean $ fmap (weight . (+ negate mean) . toRational) foldable where
mean :: Rational
mean = getMean foldable
getVariance :: (
Data.Foldable.Foldable foldable,
Fractional variance,
Functor foldable,
Real value
) => foldable value -> variance
getVariance = getDispersionFromMean Math.Power.square
getStandardDeviation :: (
Data.Foldable.Foldable foldable,
Floating result,
Functor foldable,
Real value
) => foldable value -> result
getStandardDeviation = sqrt . getVariance
getAverageAbsoluteDeviation :: (
Data.Foldable.Foldable foldable,
Fractional result,
Functor foldable,
Real value
) => foldable value -> result
getAverageAbsoluteDeviation = getDispersionFromMean abs
getCoefficientOfVariance :: (
Data.Foldable.Foldable foldable,
Eq result,
Floating result,
Functor foldable,
Real value
) => foldable value -> result
getCoefficientOfVariance l = Control.Exception.assert (mean /= 0) $ getStandardDeviation l / abs mean where
mean = getMean l
nCr :: (Math.Factorial.Algorithmic factorialAlgorithm, Integral i, Show i)
=> factorialAlgorithm
-> i
-> i
-> i
nCr _ 0 _ = 1
nCr _ _ 0 = 1
nCr factorialAlgorithm n r
| n < r = 0
| otherwise = Control.Exception.assert (n >= 0 && r >= 0) $ numerator `par` (denominator `pseq` numerator `div` denominator)
where
[smaller, bigger] = Data.List.sort [r, n r]
numerator = Math.Implementations.Factorial.risingFactorial (succ bigger) (n bigger)
denominator = Math.Factorial.factorial factorialAlgorithm smaller
nPr :: (Integral i, Show i)
=> i
-> i
-> i
nPr 0 _ = 1
nPr _ 0 = 1
nPr n r
| n < r = 0
| otherwise = Control.Exception.assert (n >= 0 && r >= 0) $ Math.Implementations.Factorial.fallingFactorial n r