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 #-}
18 module Gargantext.Core.Text.List.Group
21 import Control.Lens (set)
24 import Data.Text (Text)
25 import Gargantext.Core.Types (ListType(..))
26 import Gargantext.Database.Admin.Types.Node (NodeId)
27 import Gargantext.Core.Text.List.Social.Scores (FlowListScores(..))
28 import Gargantext.Core.Text.List.Group.WithStem
29 import Gargantext.Core.Text.List.Group.WithScores
30 import Gargantext.Prelude
31 import qualified Data.Set as Set
32 import qualified Data.Map as Map
33 import qualified Data.List as List
35 ------------------------------------------------------------------------
36 toGroupedText :: GroupedTextParams a b
37 -> Map Text FlowListScores
38 -> Map Text (Set NodeId)
39 -> Map Stem (GroupedText Int)
40 toGroupedText groupParams scores =
41 (groupWithStem groupParams) . (groupWithScores scores)
44 ------------------------------------------------------------------------
46 toGroupedText_test :: Bool -- Map Stem (GroupedText Int)
48 -- fromGroupedScores $ fromListScores from
49 toGroupedText params from datas == result
51 params = GroupedTextParams identity (Set.size . snd) fst snd
52 from :: Map Text FlowListScores
53 from = Map.fromList [("A. Rahmani",FlowListScores {_fls_parents = Map.fromList [("T. Reposeur",1)]
54 ,_fls_listType = Map.fromList [(MapTerm,2)]})
55 ,("B. Tamain",FlowListScores {_fls_parents = Map.fromList [("T. Reposeur",1)]
56 , _fls_listType = Map.fromList [(MapTerm,2)]})
59 datas :: Map Text (Set NodeId)
60 datas = Map.fromList [("A. Rahmani" , Set.fromList [1,2])
61 ,("T. Reposeur", Set.fromList [3,4])
62 ,("B. Tamain" , Set.fromList [5,6])
66 result :: Map Stem (GroupedText Int)
67 result = Map.fromList [("A. Rahmani",GroupedText {_gt_listType = Nothing
68 ,_gt_label = "A. Rahmani"
70 ,_gt_children = Set.empty
72 ,_gt_stem = "A. Rahmani"
73 ,_gt_nodes = Set.fromList [1,2]
76 ,("B. Tamain",GroupedText {_gt_listType = Nothing
77 , _gt_label = "B. Tamain"
79 , _gt_children = Set.empty
81 , _gt_stem = "B. Tamain"
82 , _gt_nodes = Set.fromList [5,6]
85 ,("T. Reposeur",GroupedText {_gt_listType = Nothing
86 ,_gt_label = "T. Reposeur"
88 ,_gt_children = Set.fromList ["A. Rahmani","B. Tamain"]
90 ,_gt_stem = "T. Reposeur"
91 ,_gt_nodes = Set.fromList [1..6]
96 ------------------------------------------------------------------------
98 addListType :: Map Text ListType -> GroupedText a -> GroupedText a
99 addListType m g = set gt_listType (hasListType m g) g
101 hasListType :: Map Text ListType -> GroupedText a -> Maybe ListType
102 hasListType m' (GroupedText _ label _ g' _ _ _) =
103 List.foldl' (<>) Nothing
104 $ map (\t -> Map.lookup t m')
106 $ Set.insert label g'