]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Core/Viz/Phylo/SynchronicClustering.hs
parameter change in the sensibility for WeightedLogSim and WeightedLogJaccard similar...
[gargantext.git] / src / Gargantext / Core / Viz / Phylo / SynchronicClustering.hs
1 {-|
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
8 Portability : POSIX
9 -}
10
11
12 module Gargantext.Core.Viz.Phylo.SynchronicClustering where
13
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)
19
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)
22
23 import Control.Lens hiding (Level)
24 import Control.Parallel.Strategies (parList, rdeepseq, using)
25 -- import Debug.Trace (trace)
26
27 import qualified Data.Map as Map
28
29
30 -------------------------
31 -- | New Level Maker | --
32 -------------------------
33
34
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)
41 ((snd $ fst id),bId)
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)
46 where
47 --------------------
48 bId :: [Int]
49 bId = mergeBranchIds $ map (\g -> snd $ g ^. phylo_groupBranchId) childs
50 --------------------
51 updatePointers :: [Pointer] -> [Pointer]
52 updatePointers pointers = map (\(pId,w) -> (mapIds ! pId,w)) pointers
53 --------------------
54 mergeAncestors :: [Pointer] -> [Pointer]
55 mergeAncestors pointers = Map.toList $ fromListWith max pointers
56
57
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
63
64
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
77
78 newPeriods = fromListWith (++) $ map (\g -> (g ^. phylo_groupPeriod, [g])) newGroups
79 in traceSynchronyEnd
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
84 (\phyloLvl ->
85 if member (phyloLvl ^. phylo_levelPeriod) newPeriods
86 then phyloLvl & phylo_levelGroups
87 .~ fromList (map (\g -> (getGroupId g, g)) $ newPeriods ! (phyloLvl ^. phylo_levelPeriod))
88 else phyloLvl)
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
93
94 --------------------
95 -- | Clustering | --
96 --------------------
97
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
103 where
104 pairs :: [PhyloGroup] -> [(PhyloGroup,PhyloGroup)]
105 pairs gs = filter (\(g,g') -> (not . null) $ intersect (g ^. phylo_groupNgrams) (g' ^. phylo_groupNgrams)) (listToCombi' gs)
106
107
108 toDiamonds :: [PhyloGroup] -> [[PhyloGroup]]
109 toDiamonds groups = foldl' (\acc groups' ->
110 acc ++ ( elems
111 $ Map.filter (\v -> length v > 1)
112 $ fromListWith (++)
113 $ foldl' (\acc' g ->
114 acc' ++ (map (\(id,_) -> (id,[g]) ) $ g ^. phylo_groupPeriodChilds)) [] groups')) []
115 $ elems
116 $ Map.filter (\v -> length v > 1)
117 $ fromListWith (++)
118 $ foldl' (\acc g -> acc ++ (map (\(id,_) -> (id,[g]) ) $ g ^. phylo_groupPeriodParents) ) [] groups
119
120
121 groupsToEdges :: Proximity -> Synchrony -> Double -> Map Int Double -> [PhyloGroup] -> [((PhyloGroup,PhyloGroup),Double)]
122 groupsToEdges prox sync nbDocs diago groups =
123 case sync of
124 ByProximityThreshold thr sens _ strat ->
125 filter (\(_,w) -> w >= thr)
126 $ toEdges sens
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
133 where
134 toEdges :: Double -> [(PhyloGroup,PhyloGroup)] -> [((PhyloGroup,PhyloGroup),Double)]
135 toEdges sens edges =
136 case prox of
137 WeightedLogJaccard _ -> map (\(g,g') ->
138 ((g,g'), weightedLogJaccard' (1 / sens) nbDocs diago
139 (g ^. phylo_groupNgrams) (g' ^. phylo_groupNgrams))) edges
140 _ -> undefined
141
142 toParentId :: PhyloGroup -> PhyloGroupId
143 toParentId child = ((child ^. phylo_groupPeriod, child ^. phylo_groupLevel + 1), child ^. phylo_groupIndex)
144
145
146 reduceGroups :: Proximity -> Synchrony -> Map Date Double -> Map Date Cooc -> [PhyloGroup] -> [PhyloGroup]
147 reduceGroups prox sync docs diagos branch =
148 -- 1) reduce a branch as a set of periods & groups
149 let periods = fromListWith (++)
150 $ map (\g -> (g ^. phylo_groupPeriod,[g])) branch
151 in (concat . concat . elems)
152 $ mapWithKey (\prd groups ->
153 -- 2) for each period, transform the groups as a proximity graph filtered by a threshold
154 let diago = reduceDiagos $ filterDiago diagos [prd]
155 edges = groupsToEdges prox sync ((sum . elems) $ restrictKeys docs $ periodsToYears [prd]) diago groups
156 in map (\comp ->
157 -- 4) add to each groups their futur level parent group
158 let parentId = toParentId (head' "parentId" comp)
159 in map (\g -> g & phylo_groupLevelParents %~ (++ [(parentId,1)]) ) comp )
160 -- 3) reduce the graph a a set of related components
161 $ toRelatedComponents groups edges) periods
162
163
164 adjustClustering :: Synchrony -> [[PhyloGroup]] -> [[PhyloGroup]]
165 adjustClustering sync branches = case sync of
166 ByProximityThreshold _ _ scope _ -> case scope of
167 SingleBranch -> branches
168 SiblingBranches -> groupBy (\g g' -> (last' "adjustClustering" $ (g ^. phylo_groupMeta) ! "breaks")
169 == (last' "adjustClustering" $ (g' ^. phylo_groupMeta) ! "breaks"))
170 $ sortOn _phylo_groupBranchId $ concat branches
171 AllBranches -> [concat branches]
172 ByProximityDistribution _ _ -> branches
173
174
175 levelUpAncestors :: [PhyloGroup] -> [PhyloGroup]
176 levelUpAncestors groups =
177 -- 1) create an associative map of (old,new) ids
178 let ids' = fromList $ map (\g -> (getGroupId g, fst $ head' "levelUpAncestors" ( g ^. phylo_groupLevelParents))) groups
179 in map (\g ->
180 let id' = ids' ! (getGroupId g)
181 ancestors = g ^. phylo_groupAncestors
182 -- 2) level up the ancestors ids and filter the ones that will be merged
183 ancestors' = filter (\(id,_) -> id /= id') $ map (\(id,w) -> (ids' ! id,w)) ancestors
184 in g & phylo_groupAncestors .~ ancestors'
185 ) groups
186
187 synchronicClustering :: Phylo -> Phylo
188 synchronicClustering phylo =
189 let prox = phyloProximity $ getConfig phylo
190 sync = phyloSynchrony $ getConfig phylo
191 docs = phylo ^. phylo_timeDocs
192 diagos = map coocToDiago $ phylo ^. phylo_timeCooc
193 newBranches = map (\branch -> levelUpAncestors $ reduceGroups prox sync docs diagos branch)
194 $ map processDynamics
195 $ adjustClustering sync
196 $ phyloToLastBranches
197 $ traceSynchronyStart phylo
198 newBranches' = newBranches `using` parList rdeepseq
199 in toNextLevel' phylo $ concat newBranches'
200
201
202 -- synchronicDistance :: Phylo -> Level -> String
203 -- synchronicDistance phylo lvl =
204 -- foldl' (\acc branch ->
205 -- acc <> (foldl' (\acc' period ->
206 -- acc' <> let prox = phyloProximity $ getConfig phylo
207 -- sync = phyloSynchrony $ getConfig phylo
208 -- docs = _phylo_timeDocs phylo
209 -- prd = _phylo_groupPeriod $ head' "distance" period
210 -- edges = groupsToEdges prox 0.1 (_bpt_sensibility sync)
211 -- ((sum . elems) $ restrictKeys docs $ periodsToYears [_phylo_groupPeriod $ head' "distance" period]) period
212 -- in foldl' (\mem (_,w) ->
213 -- mem <> show (prd)
214 -- <> "\t"
215 -- <> show (w)
216 -- <> "\n"
217 -- ) "" edges
218 -- ) "" $ elems $ groupByField _phylo_groupPeriod branch)
219 -- ) "period\tdistance\n" $ elems $ groupByField _phylo_groupBranchId $ getGroupsFromLevel lvl phylo