2 Module : Gargantext.Core.Viz.Phylo.SynchronicClustering
3 Description : Module dedicated to the adaptative synchronic clustering of a Phylo.
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 module Gargantext.Core.Viz.Phylo.SynchronicClustering where
14 import Gargantext.Prelude
15 import Gargantext.Core.Viz.AdaptativePhylo
16 import Gargantext.Core.Viz.Phylo.PhyloTools
17 import Gargantext.Core.Viz.Phylo.TemporalMatching (weightedLogJaccard', filterDiago, reduceDiagos)
18 import Gargantext.Core.Viz.Phylo.PhyloExport (processDynamics)
20 import Data.List ((++), null, intersect, nub, concat, sort, sortOn, groupBy)
21 import Data.Map (Map, fromList, fromListWith, foldlWithKey, (!), insert, empty, restrictKeys, elems, mapWithKey, member)
23 import Control.Lens hiding (Level)
24 import Control.Parallel.Strategies (parList, rdeepseq, using)
25 -- import Debug.Trace (trace)
27 import qualified Data.Map as Map
30 -------------------------
31 -- | New Level Maker | --
32 -------------------------
35 mergeGroups :: [Cooc] -> PhyloGroupId -> Map PhyloGroupId PhyloGroupId -> [PhyloGroup] -> PhyloGroup
36 mergeGroups coocs id mapIds childs =
37 let ngrams = (sort . nub . concat) $ map _phylo_groupNgrams childs
38 in PhyloGroup (fst $ fst id) (snd $ fst id) (snd id) ""
39 (sum $ map _phylo_groupSupport childs) ngrams
40 (ngramsToCooc ngrams coocs)
42 (mergeMeta bId childs) [] (map (\g -> (getGroupId g, 1)) childs)
43 (updatePointers $ concat $ map _phylo_groupPeriodParents childs)
44 (updatePointers $ concat $ map _phylo_groupPeriodChilds childs)
45 (mergeAncestors $ concat $ map _phylo_groupAncestors childs)
49 bId = mergeBranchIds $ map (\g -> snd $ g ^. phylo_groupBranchId) childs
51 updatePointers :: [Pointer] -> [Pointer]
52 updatePointers pointers = map (\(pId,w) -> (mapIds ! pId,w)) pointers
54 mergeAncestors :: [Pointer] -> [Pointer]
55 mergeAncestors pointers = Map.toList $ fromListWith max pointers
58 addPhyloLevel :: Level -> Phylo -> Phylo
59 addPhyloLevel lvl phylo =
60 over ( phylo_periods . traverse )
61 (\phyloPrd -> phyloPrd & phylo_periodLevels
62 %~ (insert (phyloPrd ^. phylo_periodPeriod, lvl) (PhyloLevel (phyloPrd ^. phylo_periodPeriod) lvl empty))) phylo
65 toNextLevel' :: Phylo -> [PhyloGroup] -> Phylo
66 toNextLevel' phylo groups =
67 let curLvl = getLastLevel phylo
68 oldGroups = fromList $ map (\g -> (getGroupId g, getLevelParentId g)) groups
69 newGroups = concat $ groupsToBranches
70 $ fromList $ map (\g -> (getGroupId g, g))
71 $ foldlWithKey (\acc id groups' ->
72 -- 4) create the parent group
73 let parent = mergeGroups (elems $ restrictKeys (phylo ^. phylo_timeCooc) $ periodsToYears [(fst . fst) id]) id oldGroups groups'
74 in acc ++ [parent]) []
75 -- 3) group the current groups by parentId
76 $ fromListWith (++) $ map (\g -> (getLevelParentId g, [g])) groups
78 newPeriods = fromListWith (++) $ map (\g -> (g ^. phylo_groupPeriod, [g])) newGroups
80 $ over ( phylo_periods . traverse . phylo_periodLevels . traverse
81 -- 6) update each period at curLvl + 1
82 . filtered (\phyloLvl -> phyloLvl ^. phylo_levelLevel == (curLvl + 1)))
83 -- 7) by adding the parents
85 if member (phyloLvl ^. phylo_levelPeriod) newPeriods
86 then phyloLvl & phylo_levelGroups
87 .~ fromList (map (\g -> (getGroupId g, g)) $ newPeriods ! (phyloLvl ^. phylo_levelPeriod))
89 -- 2) add the curLvl + 1 phyloLevel to the phylo
90 $ addPhyloLevel (curLvl + 1)
91 -- 1) update the current groups (with level parent pointers) in the phylo
92 $ updatePhyloGroups curLvl (fromList $ map (\g -> (getGroupId g, g)) groups) phylo
98 toPairs :: SynchronyStrategy -> [PhyloGroup] -> [(PhyloGroup,PhyloGroup)]
99 toPairs strategy groups = case strategy of
100 MergeRegularGroups -> pairs
101 $ filter (\g -> all (== 3) $ (g ^. phylo_groupMeta) ! "dynamics") groups
102 MergeAllGroups -> pairs groups
104 pairs :: [PhyloGroup] -> [(PhyloGroup,PhyloGroup)]
105 pairs gs = filter (\(g,g') -> (not . null) $ intersect (g ^. phylo_groupNgrams) (g' ^. phylo_groupNgrams)) (listToCombi' gs)
108 toDiamonds :: [PhyloGroup] -> [[PhyloGroup]]
109 toDiamonds groups = foldl' (\acc groups' ->
111 $ Map.filter (\v -> length v > 1)
114 acc' ++ (map (\(id,_) -> (id,[g]) ) $ g ^. phylo_groupPeriodChilds)) [] groups')) []
116 $ Map.filter (\v -> length v > 1)
118 $ foldl' (\acc g -> acc ++ (map (\(id,_) -> (id,[g]) ) $ g ^. phylo_groupPeriodParents) ) [] groups
121 groupsToEdges :: Proximity -> Synchrony -> Double -> Map Int Double -> [PhyloGroup] -> [((PhyloGroup,PhyloGroup),Double)]
122 groupsToEdges prox sync nbDocs diago groups =
124 ByProximityThreshold thr sens _ strat ->
125 filter (\(_,w) -> w >= thr)
127 $ toPairs strat groups
128 ByProximityDistribution sens strat ->
129 let diamonds = sortOn snd
130 $ toEdges sens $ concat
131 $ map (\gs -> toPairs strat gs) $ toDiamonds groups
132 in take (div (length diamonds) 2) diamonds
134 toEdges :: Double -> [(PhyloGroup,PhyloGroup)] -> [((PhyloGroup,PhyloGroup),Double)]
137 WeightedLogJaccard _ -> map (\(g,g') ->
138 ((g,g'), weightedLogJaccard' (sens) nbDocs diago
139 (g ^. phylo_groupNgrams) (g' ^. phylo_groupNgrams))) edges
140 WeightedLogSim _ -> map (\(g,g') ->
141 ((g,g'), weightedLogJaccard' (1 / sens) nbDocs diago
142 (g ^. phylo_groupNgrams) (g' ^. phylo_groupNgrams))) edges
146 toParentId :: PhyloGroup -> PhyloGroupId
147 toParentId child = ((child ^. phylo_groupPeriod, child ^. phylo_groupLevel + 1), child ^. phylo_groupIndex)
150 reduceGroups :: Proximity -> Synchrony -> Map Date Double -> Map Date Cooc -> [PhyloGroup] -> [PhyloGroup]
151 reduceGroups prox sync docs diagos branch =
152 -- 1) reduce a branch as a set of periods & groups
153 let periods = fromListWith (++)
154 $ map (\g -> (g ^. phylo_groupPeriod,[g])) branch
155 in (concat . concat . elems)
156 $ mapWithKey (\prd groups ->
157 -- 2) for each period, transform the groups as a proximity graph filtered by a threshold
158 let diago = reduceDiagos $ filterDiago diagos [prd]
159 edges = groupsToEdges prox sync ((sum . elems) $ restrictKeys docs $ periodsToYears [prd]) diago groups
161 -- 4) add to each groups their futur level parent group
162 let parentId = toParentId (head' "parentId" comp)
163 in map (\g -> g & phylo_groupLevelParents %~ (++ [(parentId,1)]) ) comp )
164 -- 3) reduce the graph a a set of related components
165 $ toRelatedComponents groups edges) periods
168 adjustClustering :: Synchrony -> [[PhyloGroup]] -> [[PhyloGroup]]
169 adjustClustering sync branches = case sync of
170 ByProximityThreshold _ _ scope _ -> case scope of
171 SingleBranch -> branches
172 SiblingBranches -> groupBy (\g g' -> (last' "adjustClustering" $ (g ^. phylo_groupMeta) ! "breaks")
173 == (last' "adjustClustering" $ (g' ^. phylo_groupMeta) ! "breaks"))
174 $ sortOn _phylo_groupBranchId $ concat branches
175 AllBranches -> [concat branches]
176 ByProximityDistribution _ _ -> branches
179 levelUpAncestors :: [PhyloGroup] -> [PhyloGroup]
180 levelUpAncestors groups =
181 -- 1) create an associative map of (old,new) ids
182 let ids' = fromList $ map (\g -> (getGroupId g, fst $ head' "levelUpAncestors" ( g ^. phylo_groupLevelParents))) groups
184 let id' = ids' ! (getGroupId g)
185 ancestors = g ^. phylo_groupAncestors
186 -- 2) level up the ancestors ids and filter the ones that will be merged
187 ancestors' = filter (\(id,_) -> id /= id') $ map (\(id,w) -> (ids' ! id,w)) ancestors
188 in g & phylo_groupAncestors .~ ancestors'
191 synchronicClustering :: Phylo -> Phylo
192 synchronicClustering phylo =
193 let prox = phyloProximity $ getConfig phylo
194 sync = phyloSynchrony $ getConfig phylo
195 docs = phylo ^. phylo_timeDocs
196 diagos = map coocToDiago $ phylo ^. phylo_timeCooc
197 newBranches = map (\branch -> reduceGroups prox sync docs diagos branch)
198 $ map processDynamics
199 $ adjustClustering sync
200 $ phyloToLastBranches
201 $ traceSynchronyStart phylo
202 newBranches' = newBranches `using` parList rdeepseq
203 in toNextLevel' phylo $ levelUpAncestors $ concat newBranches'
206 -- synchronicDistance :: Phylo -> Level -> String
207 -- synchronicDistance phylo lvl =
208 -- foldl' (\acc branch ->
209 -- acc <> (foldl' (\acc' period ->
210 -- acc' <> let prox = phyloProximity $ getConfig phylo
211 -- sync = phyloSynchrony $ getConfig phylo
212 -- docs = _phylo_timeDocs phylo
213 -- prd = _phylo_groupPeriod $ head' "distance" period
214 -- edges = groupsToEdges prox 0.1 (_bpt_sensibility sync)
215 -- ((sum . elems) $ restrictKeys docs $ periodsToYears [_phylo_groupPeriod $ head' "distance" period]) period
216 -- in foldl' (\mem (_,w) ->
222 -- ) "" $ elems $ groupByField _phylo_groupPeriod branch)
223 -- ) "period\tdistance\n" $ elems $ groupByField _phylo_groupBranchId $ getGroupsFromLevel lvl phylo