]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Data/HashMap/Strict/Utils.hs
[OPTIM] HashMap Ngrams ...
[gargantext.git] / src / Gargantext / Data / HashMap / Strict / Utils.hs
1 module Gargantext.Data.HashMap.Strict.Utils where
2
3 import Data.HashMap.Strict (HashMap)
4 import Data.Hashable (Hashable)
5 import Gargantext.Prelude
6 import qualified Data.HashMap.Strict as HashMap
7
8 ------------------------------------------------------------------------
9 unionsWith :: (Foldable f, Eq k, Hashable k) => (a->a->a) -> f (HashMap k a) -> HashMap k a
10 unionsWith f = foldl' (HashMap.unionWith f) HashMap.empty
11
12 ------------------------------------------------------------------------
13 -- | Partition the map according to some predicate. The first map contains all
14 -- elements that satisfy the predicate, the second all elements that fail the
15 -- predicate.
16 partition :: (Ord k, Hashable k) => (a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a)
17 partition p m = (HashMap.filter p m, HashMap.filter (not . p) m)
18
19 -- | Partition the map according to some predicate. The first map contains all
20 -- elements that satisfy the predicate, the second all elements that fail the
21 -- predicate.
22 partitionWithKey :: (Ord a, Hashable k) => (k -> a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a)
23 partitionWithKey p m = (HashMap.filterWithKey p m, HashMap.filterWithKey (\k -> not . p k) m)
24
25
26 mapKeys :: (Ord k2, Hashable k2) => (k1->k2) -> HashMap k1 a -> HashMap k2 a
27 mapKeys f = HashMap.fromList . HashMap.foldrWithKey (\k x xs -> (f k, x) : xs) []
28
29 ------------------------------------------------------------------------
30 -- getKeyWithMaxValue :: Hashable k => HashMap k a -> Maybe k
31 getKeysOrderedByValueMaxFirst :: (Ord k, Hashable k, Ord a) => HashMap k a -> [k]
32 getKeysOrderedByValueMaxFirst m = go [] Nothing (HashMap.toList m)
33 where
34 go ks _ [] = ks
35 go ks Nothing ((k,v):rest) = go (k:ks) (Just v) rest
36 go ks (Just u) ((k,v):rest)
37 | v < u = go ks (Just u) rest
38 | v > u = go [k] (Just v) rest
39 | otherwise = go (k:ks) (Just v) rest
40