2 Module : Gargantext.Core.Text.List.Group
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE TemplateHaskell #-}
13 {-# LANGUAGE ConstraintKinds #-}
14 {-# LANGUAGE TypeFamilies #-}
15 {-# LANGUAGE FunctionalDependencies #-}
16 {-# LANGUAGE InstanceSigs #-}
18 module Gargantext.Core.Text.List.Group
21 import Control.Lens (set, view, over)
24 import Data.Maybe (fromMaybe)
25 import Data.Monoid (Monoid, mempty)
26 import Data.Text (Text)
27 import Gargantext.Core.Types (ListType(..))
28 import Gargantext.Database.Admin.Types.Node (NodeId)
29 import Gargantext.Core.Text.List.Social.Prelude
30 import Gargantext.Core.Text.List.Group.Prelude
31 import Gargantext.Core.Text.List.Group.WithStem
32 import Gargantext.Core.Text.List.Group.WithScores
33 import Gargantext.Prelude
34 import qualified Data.Set as Set
35 import qualified Data.Map as Map
36 import qualified Data.List as List
38 ------------------------------------------------------------------------
39 -- | TODO add group with stemming
40 toGroupedTree :: (Ord a, Monoid a, GroupWithStem a)
42 -> FlowCont Text FlowListScores
44 -- -> Map Text (GroupedTreeScores (Set NodeId))
45 -> FlowCont Text (GroupedTreeScores a)
46 toGroupedTree groupParams flc scores = {-view flc_scores-} flow2
48 flow1 = groupWithScores' flc scoring
49 scoring t = fromMaybe mempty $ Map.lookup t scores
51 flow2 = case (view flc_cont flow1) == Map.empty of
53 False -> groupWithStem' groupParams flow1
56 DM.foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a
59 setScoresWith :: (Ord a, Ord b)
60 => (Text -> (GroupedTreeScores a) -> (GroupedTreeScores b))
61 -> Map Text (GroupedTreeScores a)
62 -> Map Text (GroupedTreeScores b)
63 setScoresWith = Map.mapWithKey
66 Map.foldlWithKey (\k v ->
67 {- over gts'_children (setScoresWith fun)
68 $ over gts'_score (fun k)
70 set gts'_score Set.empty -- (fun k)
75 ------------------------------------------------------------------------