module Language.Copilot.Libs.Statistics
(max, min, sum, mean, meanNow) where
import Prelude (Int, ($), foldl1, fromIntegral, foldl, error, length)
import qualified Language.Atom as A
import Language.Copilot.Libs.ErrorChks (nOneChk)
import Language.Copilot.Core
import Language.Copilot.Language
foldDrops :: (Streamable a) => Int -> (Spec a -> Spec a -> Spec a) -> Spec a -> Spec a
foldDrops n f s = foldl1 f [drop x s | x <- [0..(n1)]]
sum :: (Streamable a, A.NumE a) => Int -> Spec a -> Spec a
sum n s =
nOneChk "sum" n $ foldDrops n (+) s
max :: (Streamable a, A.NumE a) => Int -> Spec a -> Spec a
max n s =
nOneChk "max" n $ foldDrops n largest s
where largest = \ x y -> mux (x <= y) y x
min :: (Streamable a, A.NumE a) => Int -> Spec a -> Spec a
min n s =
nOneChk "max" n $ foldDrops n smallest s
where smallest = \ x y -> mux (x <= y) x y
mean :: (Streamable a, Fractional a, A.NumE a) => Int -> Spec a -> Spec a
mean n s =
nOneChk "mean" n $ (sum n s) / (fromIntegral n)
meanNow :: (Streamable a, A.IntegralE a) => [Spec a] -> Spec a
meanNow [] = error
"Error in majority: list of arguments must be nonempty."
meanNow ls =
(foldl (+) 0 ls) `div` (fromIntegral $ length ls)