1 {-# LANGUAGE NoImplicitPrelude #-}
2 {-# LANGUAGE ExistentialQuantification #-}
3 {-# LANGUAGE BangPatterns #-}
4 {-# LANGUAGE RankNTypes #-}
6 module Data.Gargantext.Utils.Count (head, last, all, any, sum, product, length)
10 import Protolude hiding ((<>), head, last, all, any, sum, product, length)
12 import qualified Data.Foldable
13 import Control.Lens (Getting, foldMapOf)
15 data Fold i o = forall m . Monoid m => Fold (i -> m) (m -> o)
17 instance Functor (Fold i) where
18 fmap k (Fold tally summarize) = Fold tally (k . summarize)
20 instance Applicative (Fold i) where
21 pure o = Fold (\_ -> ()) (\_ -> o)
23 Fold tallyF summarizeF <*> Fold tallyX summarizeX = Fold tally summarize
25 tally i = (tallyF i, tallyX i)
26 summarize (nF, nX) = summarizeF nF (summarizeX nX)
28 focus :: (forall m . Monoid m => Getting m b a) -> Fold a o -> Fold b o
29 focus lens (Fold tally summarize) = Fold (foldMapOf lens tally) summarize
32 fold :: Fold i o -> [i] -> o
33 fold (Fold tally summarize) is = summarize (reduce (map tally is))
35 reduce = Data.Foldable.foldl' (<>) mempty
38 head :: Fold a (Maybe a)
39 head = Fold (First . Just) getFirst
41 last :: Fold a (Maybe a)
42 last = Fold (Last . Just) getLast
44 all :: (a -> Bool) -> Fold a Bool
45 all predicate = Fold (All . predicate) getAll
47 any :: (a -> Bool) -> Fold a Bool
48 any predicate = Fold (Any . predicate) getAny
50 sum :: Num n => Fold n n
53 product :: Num n => Fold n n
54 product = Fold Product getProduct
56 length :: Num n => Fold i n
57 length = Fold (\_ -> Sum 1) getSum
60 -- | Average function optimized (/!\ need to test it)
61 data Average a = Average { numerator :: !a, denominator :: !Int }
63 instance Num a => Monoid (Average a) where
65 mappend (Average xL nL) (Average xR nR) = Average (xL + xR) (nL + nR)
67 average :: Fractional a => Fold a a
68 average = Fold tally summarize
71 summarize (Average numerator denominator) =
72 numerator / fromIntegral denominator