Commit 4ab99758 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] HashMap lacking functions in main lib

parent 252b3ef9
...@@ -20,7 +20,7 @@ import qualified Data.List as DL ...@@ -20,7 +20,7 @@ import qualified Data.List as DL
import qualified Data.Vector as DV import qualified Data.Vector as DV
import qualified Data.Map as M import qualified Data.Map as M
import Gargantext.Core.Text.Metrics.Freq as F import Gargantext.Core.Text.Metrics.Utils as Utils
import Gargantext.Core.Text.Corpus.Parsers.CSV as CSV import Gargantext.Core.Text.Corpus.Parsers.CSV as CSV
data School = School { school_shortName :: Text data School = School { school_shortName :: Text
...@@ -115,7 +115,7 @@ publisBySchool hal_data' = Gargantext.Prelude.map (\(i,n) -> (M.lookup i mapIdSc ...@@ -115,7 +115,7 @@ publisBySchool hal_data' = Gargantext.Prelude.map (\(i,n) -> (M.lookup i mapIdSc
$ DL.reverse $ DL.reverse
$ DL.sortOn snd $ DL.sortOn snd
$ M.toList $ M.toList
$ F.freq $ Utils.freq
$ DL.concat $ DL.concat
$ DV.toList $ DV.toList
$ DV.map (\n -> splitOn ( ", ") (csvHal_instStructId_i n) ) $ DV.map (\n -> splitOn ( ", ") (csvHal_instStructId_i n) )
......
...@@ -27,7 +27,6 @@ import Data.Semigroup (Semigroup(..)) ...@@ -27,7 +27,6 @@ import Data.Semigroup (Semigroup(..))
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.Core.Text.Metrics.Freq (getMaxFromMap)
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Data.HashMap.Strict.Utils as HashMap import qualified Gargantext.Data.HashMap.Strict.Utils as HashMap
...@@ -114,19 +113,13 @@ parentUnionsExcl = HashMap.unions ...@@ -114,19 +113,13 @@ parentUnionsExcl = HashMap.unions
keyWithMaxValue :: (Ord a, Ord b, Num b, Hashable a) keyWithMaxValue :: (Ord a, Ord b, Num b, Hashable a)
=> HashMap a b -> Maybe a => HashMap a b -> Maybe a
keyWithMaxValue m = do keyWithMaxValue m = do
maxKey <- headMay $ HashMap.getKeyWithMaxValue m maxKey <- headMay $ HashMap.getKeysOrderedByValueMaxFirst m
maxValue <- HashMap.lookup maxKey m maxValue <- HashMap.lookup maxKey m
if maxValue > 0 if maxValue > 0
then pure maxKey then pure maxKey
else Nothing else Nothing
findMax :: (Ord b, Num b, Hashable a) => HashMap a b -> Maybe (a,b)
findMax m = case HashMap.null m of
True -> Nothing
False -> Just $ HashMap.findMax m
------------------------------------------------------------------------ ------------------------------------------------------------------------
unPatchMapToHashMap :: (Ord a, Hashable a) => PatchMap a b -> HashMap a b unPatchMapToHashMap :: (Ord a, Hashable a) => PatchMap a b -> HashMap a b
unPatchMapToHashMap = HashMap.fromList . PatchMap.toList unPatchMapToHashMap = HashMap.fromList . PatchMap.toList
......
...@@ -25,20 +25,17 @@ module Gargantext.Core.Text.Metrics.FrequentItemSet ...@@ -25,20 +25,17 @@ module Gargantext.Core.Text.Metrics.FrequentItemSet
) )
where where
import Data.List (concat, null)
import Data.Map.Strict (Map)
import Data.Maybe (catMaybes)
import Data.Set (Set)
import Gargantext.Prelude
import HLCM
import Prelude (Functor(..)) -- TODO import Prelude (Functor(..)) -- TODO
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map)
import qualified Data.Set as Set import qualified Data.Set as Set
import Data.Set (Set)
import qualified Data.Vector as V import qualified Data.Vector as V
import Data.List (concat, null)
import Data.Maybe (catMaybes)
import HLCM
import Gargantext.Prelude
data Size = Point Int | Segment Int Int data Size = Point Int | Segment Int Int
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
{-| {-|
Module : Gargantext.Core.Text.Metrics.Freq Module : Gargantext.Core.Text.Metrics.Utils
Description : Some functions to count. Description : Some functions to count.
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -10,7 +10,7 @@ Portability : POSIX ...@@ -10,7 +10,7 @@ Portability : POSIX
-} -}
module Gargantext.Core.Text.Metrics.Freq where module Gargantext.Core.Text.Metrics.Utils where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Map (empty, Map, insertWith, toList) import Data.Map (empty, Map, insertWith, toList)
......
module Gargantext.Data.HashMap.Strict.Utils where module Gargantext.Data.HashMap.Strict.Utils where
import Data.Hashable (Hashable)
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM import Data.Hashable (Hashable)
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.HashMap.Strict as HashMap
------------------------------------------------------------------------
unionsWith :: (Foldable f, Eq k, Hashable k) => (a->a->a) -> f (HashMap k a) -> HashMap k a unionsWith :: (Foldable f, Eq k, Hashable k) => (a->a->a) -> f (HashMap k a) -> HashMap k a
unionsWith f = foldl' (HM.unionWith f) HM.empty unionsWith f = foldl' (HashMap.unionWith f) HashMap.empty
partition :: Hashable k => (a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a) ------------------------------------------------------------------------
partition = undefined -- | Partition the map according to some predicate. The first map contains all
-- elements that satisfy the predicate, the second all elements that fail the
-- predicate.
partitionWithKey :: Hashable k => (k -> a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a) partition :: (Ord k, Hashable k) => (a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a)
partitionWithKey = undefined partition p m = (HashMap.filter p m, HashMap.filter (not . p) m)
findMax :: Hashable k => HashMap k a -> (k, a) -- | Partition the map according to some predicate. The first map contains all
findMax = undefined -- elements that satisfy the predicate, the second all elements that fail the
-- predicate.
partitionWithKey :: (Ord a, Hashable k) => (k -> a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a)
partitionWithKey p m = (HashMap.filterWithKey p m, HashMap.filterWithKey (\k -> not . p k) m)
------------------------------------------------------------------------
-- getKeyWithMaxValue :: Hashable k => HashMap k a -> Maybe k -- getKeyWithMaxValue :: Hashable k => HashMap k a -> Maybe k
getKeyWithMaxValue :: Hashable k => HashMap k a -> [k] getKeysOrderedByValueMaxFirst :: (Ord k, Hashable k, Ord a) => HashMap k a -> [k]
getKeyWithMaxValue = undefined getKeysOrderedByValueMaxFirst m = go [] Nothing (HashMap.toList m)
where
go ks _ [] = ks
go ks Nothing ((k,v):rest) = go (k:ks) (Just v) rest
go ks (Just u) ((k,v):rest)
| v < u = go ks (Just u) rest
| v > u = go [k] (Just v) rest
| otherwise = go (k:ks) (Just v) rest
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment