]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo/Example.hs
add the Metrics and the Filters
[gargantext.git] / src / Gargantext / Viz / Phylo / Example.hs
1 {-|
2 Module : Gargantext.Viz.Phylo.Example
3 Description : Phylomemy example based on history of Cleopatre.
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 -- | Cesar et Cleôpatre
11 -- Exemple de phylomemie
12 -- French without accents
13
14
15 TODO:
16 - split the functions : RAW -> Document -> Ngrams
17
18 -- reverse history: antechronologique
19 -- metrics support
20
21
22 -}
23
24 {-# LANGUAGE NoImplicitPrelude #-}
25 {-# LANGUAGE FlexibleContexts #-}
26 {-# LANGUAGE OverloadedStrings #-}
27 {-# LANGUAGE MultiParamTypeClasses #-}
28
29 module Gargantext.Viz.Phylo.Example where
30
31 import Control.Lens hiding (makeLenses, both, Level)
32
33 import Data.Bool (Bool, not)
34 import Data.List ((\\), notElem, concat, union, intersect, tails, tail, head, last, null, zip, sort, length, any, (++), (!!), nub, sortOn, reverse, splitAt, take, delete, init, groupBy)
35 import Data.Map (Map, elems, insert, member, adjust, singleton, empty, (!), keys, restrictKeys, mapWithKey, filterWithKey, mapKeys, intersectionWith, unionWith)
36 import Data.Maybe (mapMaybe,isJust,fromJust)
37 import Data.Semigroup (Semigroup)
38 import Data.Set (Set)
39 import Data.Text (Text, unwords, toLower, words)
40 import Data.Tuple (fst, snd)
41 import Data.Tuple.Extra
42 import Data.Vector (Vector, fromList, elemIndex, (!))
43
44 import Debug.Trace (trace)
45
46 import Gargantext.Prelude hiding (head)
47 import Gargantext.Text.Terms.Mono (monoTexts)
48
49 import Gargantext.Viz.Phylo
50 import Gargantext.Viz.Phylo.Aggregates.Cluster
51 import Gargantext.Viz.Phylo.Aggregates.Cooc
52 import Gargantext.Viz.Phylo.Aggregates.Document
53 import Gargantext.Viz.Phylo.Aggregates.Fis
54 import Gargantext.Viz.Phylo.BranchMaker
55 import Gargantext.Viz.Phylo.LevelMaker
56 import Gargantext.Viz.Phylo.LinkMaker
57 import Gargantext.Viz.Phylo.Metrics.Proximity
58 import Gargantext.Viz.Phylo.Metrics.Clustering
59 import Gargantext.Viz.Phylo.Tools
60
61
62 import qualified Data.Bool as Bool
63 import qualified Data.List as List
64 import qualified Data.Map as Map
65 import qualified Data.Maybe as Maybe
66 import qualified Data.Set as Set
67 import qualified Data.Tuple as Tuple
68 import qualified Data.Vector as Vector
69
70
71 ------------------------------------------------------------------------
72 -- | STEP 12 | -- Return a Phylo for upcomming visiualization tasks
73
74
75
76 -- | To transform a list of Ngrams Indexes into a Label
77 ngramsToLabel :: Vector Ngrams -> [Int] -> Text
78 ngramsToLabel ngrams l = unwords $ ngramsToText ngrams l
79
80
81 -- | To transform a list of Ngrams Indexes into a list of Text
82 ngramsToText :: Vector Ngrams -> [Int] -> [Text]
83 ngramsToText ngrams l = map (\idx -> ngrams Vector.! idx) l
84
85
86 -- | To get the nth most frequent Ngrams in a list of PhyloGroups
87 mostFreqNgrams :: Int -> [PhyloGroup] -> [Int]
88 mostFreqNgrams thr groups = map fst
89 $ take thr
90 $ reverse
91 $ sortOn snd
92 $ map (\g -> (head g,length g))
93 $ groupBy (==)
94 $ (sort . concat)
95 $ map getGroupNgrams groups
96
97
98 -- | To get the (nth `div` 2) most cooccuring Ngrams in a PhyloGroup
99 mostOccNgrams :: Int -> PhyloGroup -> [Int]
100 mostOccNgrams thr group = (nub . concat )
101 $ map (\((f,s),d) -> [f,s])
102 $ take (thr `div` 2)
103 $ reverse $ sortOn snd $ Map.toList $ getGroupCooc group
104
105
106 freqToLabel :: Int -> [PhyloGroup] -> Vector Ngrams -> Text
107 freqToLabel thr l ngs = ngramsToLabel ngs $ mostFreqNgrams thr l
108
109 --------- To Do tagger, sort et display
110
111
112 getNodeId :: PhyloNode -> PhyloGroupId
113 getNodeId n = n ^. phylo_nodeId
114
115 getSourceId :: PhyloEdge -> PhyloGroupId
116 getSourceId e = e ^. phylo_edgeSource
117
118 getTargetId :: PhyloEdge -> PhyloGroupId
119 getTargetId e = e ^. phylo_edgeTarget
120
121 getNodeBranchId :: PhyloNode -> PhyloBranchId
122 getNodeBranchId n = case n ^. phylo_nodeBranchId of
123 Nothing -> panic "[ERR][Viz.Phylo.Tools.getNodeBranchId] branchId not found"
124 Just i -> i
125
126
127 getBranchId :: PhyloBranch -> PhyloBranchId
128 getBranchId b = b ^. phylo_branchId
129
130
131 getViewBranchIds :: PhyloView -> [PhyloBranchId]
132 getViewBranchIds v = map getBranchId $ v ^. phylo_viewBranches
133
134
135 cleanNodesEdges :: PhyloView -> PhyloView -> PhyloView
136 cleanNodesEdges v v' = v' & phylo_viewNodes %~ (filter (\n -> not $ elem (getNodeId n) nIds))
137 & phylo_viewEdges %~ (filter (\e -> (not $ elem (getSourceId e) nIds)
138 && (not $ elem (getTargetId e) nIds)))
139 where
140 --------------------------------------
141 nIds :: [PhyloGroupId]
142 nIds = map getNodeId
143 $ filter (\n -> elem (getNodeBranchId n) bIds)
144 $ getNodesInBranches v
145 --------------------------------------
146 bIds :: [PhyloBranchId]
147 bIds = (getViewBranchIds v) \\ (getViewBranchIds v')
148 --------------------------------------
149
150
151 filterLonelyBranch :: Int -> Int -> Int -> [PhyloPeriodId] -> PhyloView -> PhyloView
152 filterLonelyBranch nbInf nbSup nbNs prds v = cleanNodesEdges v v'
153 where
154 --------------------------------------
155 v' :: PhyloView
156 v' = v & phylo_viewBranches %~ (filter (\b -> let ns = filter (\n -> (getBranchId b) == (getNodeBranchId n))
157 $ getNodesInBranches v
158 prds' = nub $ map (\n -> (fst . fst) $ getNodeId n) ns
159 in not (isLone ns prds')))
160 --------------------------------------
161 isLone :: [PhyloNode] -> [PhyloPeriodId] -> Bool
162 isLone ns prds' = (length ns <= nbNs)
163 && notElem (head prds') (take nbInf prds)
164 && notElem (head prds') (take nbSup $ reverse prds)
165 --------------------------------------
166
167
168 getBranchIdsWith :: Level -> Phylo -> [PhyloBranchId]
169 getBranchIdsWith lvl p = sortOn snd
170 $ mapMaybe getGroupBranchId
171 $ getGroupsWithLevel lvl p
172
173 phyloParams :: PhyloParam
174 phyloParams = PhyloParam "v0.1" (Software "Gargantext" "v4") ""
175
176 getPhyloParams :: Phylo -> PhyloParam
177 getPhyloParams p = phyloParams
178
179 initPhyloBranch :: PhyloBranchId -> Text -> PhyloBranch
180 initPhyloBranch id lbl = PhyloBranch id lbl empty
181
182 groupsToNodes :: Bool -> Bool -> Vector Ngrams -> [PhyloGroup] -> [PhyloNode]
183 groupsToNodes isR isV ns gs = map (\g -> let idxs = getGroupNgrams g
184 in PhyloNode
185 (getGroupId g)
186 (getGroupBranchId g)
187 "" idxs
188 (if isV
189 then Just (ngramsToText ns idxs)
190 else Nothing)
191 empty
192 (if (not isR)
193 then Just (head $ getGroupLevelParentsId g)
194 else Nothing)
195 ) gs
196
197
198 initPhyloEdge :: PhyloGroupId -> [Pointer] -> EdgeType -> [PhyloEdge]
199 initPhyloEdge id pts et = map (\pt -> PhyloEdge id (fst pt) et (snd pt)) pts
200
201
202 groupsToEdges :: Filiation -> EdgeType -> [PhyloGroup] -> [PhyloEdge]
203 groupsToEdges fl et gs = case fl of
204 Complete -> (groupsToEdges Ascendant et gs) ++ (groupsToEdges Descendant et gs)
205 _ -> concat
206 $ map (\g -> case fl of
207 Ascendant -> case et of
208 PeriodEdge -> initPhyloEdge (getGroupId g) (getGroupPeriodParents g) et
209 LevelEdge -> initPhyloEdge (getGroupId g) (getGroupLevelParents g) et
210 Descendant -> case et of
211 PeriodEdge -> initPhyloEdge (getGroupId g) (getGroupPeriodChilds g) et
212 LevelEdge -> initPhyloEdge (getGroupId g) (getGroupLevelChilds g) et
213 ) gs
214
215
216 addBranches :: Level -> Phylo -> [PhyloBranch]
217 addBranches lvl p = map (\id -> initPhyloBranch id "") $ nub $ getBranchIdsWith lvl p
218
219
220 initPhyloView :: Level -> Text -> Text -> Filiation -> Bool -> Phylo -> PhyloView
221 initPhyloView lvl lbl dsc fl vb p = PhyloView (getPhyloParams p) lbl dsc fl empty
222 ([] ++ (addBranches lvl p))
223 ([] ++ (groupsToNodes True vb (getFoundations p) gs))
224 ([] ++ (groupsToEdges fl PeriodEdge gs))
225 where
226 --------------------------------------
227 gs :: [PhyloGroup]
228 gs = getGroupsWithLevel lvl p
229 --------------------------------------
230
231
232 addChildNodes :: Bool -> Level -> Level -> Bool -> Filiation -> Phylo -> PhyloView -> PhyloView
233 addChildNodes shouldDo lvl lvl' vb fl p v =
234 if (not shouldDo) || (lvl == lvl')
235 then v
236 else addChildNodes shouldDo lvl (lvl' - 1) vb fl p
237 $ v & phylo_viewBranches %~ (++ (addBranches (lvl' - 1) p))
238 & phylo_viewNodes %~ (++ (groupsToNodes False vb (getFoundations p) gs'))
239 & phylo_viewEdges %~ (++ (groupsToEdges fl PeriodEdge gs'))
240 & phylo_viewEdges %~ (++ (groupsToEdges Descendant LevelEdge gs ))
241 & phylo_viewEdges %~ (++ (groupsToEdges Ascendant LevelEdge gs'))
242 where
243 --------------------------------------
244 gs :: [PhyloGroup]
245 gs = getGroupsWithLevel lvl' p
246 --------------------------------------
247 gs' :: [PhyloGroup]
248 gs' = getGroupsWithLevel (lvl' - 1) p
249 --------------------------------------
250
251
252 addBranchMeta :: PhyloBranchId -> Text -> Double -> PhyloView -> PhyloView
253 addBranchMeta id lbl val v = over (phylo_viewBranches
254 . traverse)
255 (\b -> if getBranchId b == id
256 then b & phylo_branchMeta %~ insert lbl val
257 else b) v
258
259 getNodesInBranches :: PhyloView -> [PhyloNode]
260 getNodesInBranches v = filter (\n -> isJust $ n ^. phylo_nodeBranchId)
261 $ v ^. phylo_viewNodes
262
263
264 branchAge :: PhyloView -> PhyloView
265 branchAge v = foldl (\v' b -> let bId = (fst . head) b
266 prds = sortOn fst $ map snd b
267 in addBranchMeta bId "age" ((abs . fromIntegral)
268 $ ((snd . last) prds) - ((fst . head) prds)) v') v
269 $ groupBy ((==) `on` fst)
270 $ sortOn fst
271 $ map (\n -> (getNodeBranchId n, (fst . fst) $ getNodeId n))
272 $ getNodesInBranches v
273
274
275 processMetrics :: [Metric] -> Phylo -> PhyloView -> PhyloView
276 processMetrics ms p v = foldl (\v' m -> case m of
277 BranchAge -> branchAge v'
278 _ -> panic "[ERR][Viz.Phylo.Example.processMetrics] metric not found") v ms
279
280
281 processFilters :: [QueryFilter] -> Phylo -> PhyloView -> PhyloView
282 processFilters fs p v = foldl (\v' f -> case f ^. query_filter of
283 LonelyBranch -> filterLonelyBranch (round $ (f ^. query_params) !! 0)
284 (round $ (f ^. query_params) !! 1)
285 (round $ (f ^. query_params) !! 2) (getPhyloPeriods p) v'
286 _ -> panic "[ERR][Viz.Phylo.Example.processFilters] filter not found") v fs
287
288
289 queryToView :: PhyloQuery -> Phylo -> PhyloView
290 queryToView q p = processFilters (q ^.query_filters) p
291 $ processMetrics (q ^.query_metrics) p
292 $ addChildNodes (q ^. query_childs) (q ^. query_lvl) (q ^. query_childsDepth) (q ^. query_verbose) (q ^. query_filiation) p
293 $ initPhyloView (q ^. query_lvl) "Phylo2000" "This is a Phylo" (q ^. query_filiation) (q ^. query_verbose) p
294
295
296 defaultQuery :: PhyloQuery
297 defaultQuery = PhyloQuery 3 Descendant False 0 [] [] [] Nothing Flat True
298
299
300 urlQuery :: Text
301 urlQuery = "level=3&childs=false&filter=LonelyBranchFilter(2,2,1):true&metric=BranchAge&tagger=BranchLabelFreq&tagger=GroupLabelCooc"
302
303 -- | To do : add a queryParser from an URL and then update the defaultQuery
304 urlToQuery :: Text -> PhyloQuery
305 urlToQuery url = defaultQuery
306 & query_lvl .~ 3
307 & query_childs .~ False
308 & query_metrics %~ (++ [BranchAge])
309 & query_filters %~ (++ [QueryFilter LonelyBranch [2,2,1]])
310 & query_taggers %~ (++ [BranchLabelFreq,GroupLabelCooc])
311
312
313 toPhyloView :: Text -> Phylo -> PhyloView
314 toPhyloView url p = queryToView (urlToQuery url) p
315
316
317 ------------------------------------------------------------------------
318 -- | STEP 11 | -- Incrementaly cluster the PhyloGroups n times, link them through the Periods and build level n of the Phylo
319
320
321 phylo6 :: Phylo
322 phylo6 = toNthLevel 6 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) (WeightedLogJaccard,[0.01,0]) phylo3
323
324
325 phylo3 :: Phylo
326 phylo3 = setPhyloBranches 3
327 $ interTempoMatching Childs 3 (WeightedLogJaccard,[0.01,0])
328 $ interTempoMatching Parents 3 (WeightedLogJaccard,[0.01,0])
329 $ setLevelLinks (2,3)
330 $ addPhyloLevel 3
331 (phyloToClusters 2 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) phyloBranch2)
332 phyloBranch2
333
334
335 ------------------------------------------------------------------------
336 -- | STEP 10 | -- Cluster the Fis
337
338 phyloBranch2 :: Phylo
339 phyloBranch2 = setPhyloBranches 2 phylo2_c
340
341
342 phylo2_c :: Phylo
343 phylo2_c = interTempoMatching Childs 2 (WeightedLogJaccard,[0.01,0]) phylo2_p
344
345
346 phylo2_p :: Phylo
347 phylo2_p = interTempoMatching Parents 2 (WeightedLogJaccard,[0.01,0]) phylo2_1_2
348
349
350 phylo2_1_2 :: Phylo
351 phylo2_1_2 = setLevelLinks (1,2) phylo2
352
353
354 -- | phylo2 allready contains the LevelChilds links from 2 to 1
355 phylo2 :: Phylo
356 phylo2 = addPhyloLevel 2 phyloCluster phyloBranch1
357
358
359 phyloCluster :: Map (Date,Date) [Cluster]
360 phyloCluster = phyloToClusters 1 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) phyloBranch1
361
362
363 ------------------------------------------------------------------------
364 -- | STEP 9 | -- Find the Branches
365
366
367 phyloBranch1 :: Phylo
368 phyloBranch1 = setPhyloBranches 1 phylo1_c
369
370
371 ------------------------------------------------------------------------
372 -- | STEP 8 | -- Link the PhyloGroups of level 1 through the Periods
373
374
375 phylo1_c :: Phylo
376 phylo1_c = interTempoMatching Childs 1 (WeightedLogJaccard,[0.01,0]) phylo1_p
377
378
379 phylo1_p :: Phylo
380 phylo1_p = interTempoMatching Parents 1 (WeightedLogJaccard,[0.01,0]) phylo1_0_1
381
382
383 ------------------------------------------------------------------------
384 -- | STEP 7 | -- Build the coocurency Matrix of the Phylo
385
386
387 phyloCooc :: Map (Int, Int) Double
388 phyloCooc = fisToCooc phyloFis phylo1_0_1
389
390
391 ------------------------------------------------------------------------
392 -- | STEP 6 | -- Build the level 1 of the Phylo
393
394
395 phylo1_0_1 :: Phylo
396 phylo1_0_1 = setLevelLinks (0,1) phylo1_1_0
397
398
399 phylo1_1_0 :: Phylo
400 phylo1_1_0 = setLevelLinks (1,0) phylo1
401
402
403 phylo1 :: Phylo
404 phylo1 = addPhyloLevel (1) phyloFis phylo
405
406
407 ------------------------------------------------------------------------
408 -- | STEP 5 | -- Create lists of Frequent Items Set and filter them
409
410
411 phyloFis :: Map (Date, Date) [Fis]
412 phyloFis = filterFisBySupport False 1 (filterFisByNested (docsToFis phyloDocs))
413
414
415 ------------------------------------------------------------------------
416 -- | STEP 2 | -- Init a Phylo of level 0
417
418
419 -- phylo' :: Phylo
420 -- phylo' = initPhylo 5 3 corpus actants groupNgramsWithTrees
421
422
423 phylo :: Phylo
424 phylo = addPhyloLevel 0 phyloDocs phyloBase
425
426
427 phyloDocs :: Map (Date, Date) [Document]
428 phyloDocs = corpusToDocs groupNgramsWithTrees corpus phyloBase
429
430
431 ------------------------------------------------------------------------
432 -- | STEP 1 | -- Init the Base of the Phylo from Periods and Foundations
433
434
435 phyloBase :: Phylo
436 phyloBase = initPhyloBase periods foundations
437
438
439 periods :: [(Date,Date)]
440 periods = initPeriods 5 3
441 $ both fst (head corpus,last corpus)
442
443
444 foundations :: Vector Ngrams
445 foundations = initFoundations actants
446
447
448 ------------------------------------------------------------------------
449 -- | STEP 0 | -- Let's start with an example
450
451
452 actants :: [Ngrams]
453 actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV"
454 , "Marc-Antoine", "Cesar" , "Antoine" , "Octave" , "Rome"
455 , "Alexandrie" , "Auguste" , "Pompee" , "Cassius" , "Brutus"]
456
457
458 corpus :: [(Date, Text)]
459 corpus = List.sortOn fst [ (-51,"Cleopatre règne sur l’egypte entre 51 et 30 av. J.-C. avec ses frères-epoux Ptolemee-XIII et Ptolemee-XIV, puis aux côtes du general romain Marc-Antoine. Elle est celèbre pour avoir ete la compagne de Jules Cesar puis d'Antoine, avec lesquels elle a eu plusieurs enfants. Partie prenante dans la guerre civile opposant Antoine à Octave, elle est vaincue à la bataille d'Actium en 31 av. J.-C. Sa defaite va permettre aux Romains de mener à bien la conquête de l’egypte, evenement qui marquera la fin de l'epoque hellenistique."), (-40,"Il existe relativement peu d'informations sur son sejour à Rome, au lendemain de l'assassinat de Cesar, ou sur la periode passee à Alexandrie durant l'absence d'Antoine, entre -40 et -37."), (-48,"L'historiographie antique lui est globalement defavorable car inspiree par son vainqueur, l'empereur Auguste, et par son entourage, dont l'interêt est de la noircir, afin d'en faire l'adversaire malfaisant de Rome et le mauvais genie d'Antoine. On observe par ailleurs que Cesar ne fait aucune mention de sa liaison avec elle dans les Commentaires sur la Guerre civile"), (-69,"Cleopatre est nee au cours de l'hiver -69/-686 probablement à Alexandrie."), (-48,"Pompee a en effet ete le protecteur de Ptolemee XII, le père de Cleopatre et de Ptolemee-XIII dont il se considère comme le tuteur."), (-48,"Ptolemee-XIII et Cleopatre auraient d'ailleurs aide Pompee par l'envoi d'une flotte de soixante navires."), (-48,"Mais le jeune roi Ptolemee-XIII et ses conseillers jugent sa cause perdue et pensent s'attirer les bonnes graces du vainqueur en le faisant assassiner à peine a-t-il pose le pied sur le sol egyptien, près de Peluse, le 30 juillet 48 av. J.-C., sous les yeux de son entourage."), (-48,"Cesar fait enterrer la tête de Pompee dans le bosquet de Nemesis en bordure du mur est de l'enceinte d'Alexandrie. Pour autant la mort de Pompee est une aubaine pour Cesar qui tente par ailleurs de profiter des querelles dynastiques pour annexer l’egypte."), (-48,"Il est difficile de se prononcer clairement sur les raisons qui ont pousse Cesar à s'attarder à Alexandrie. Il y a des raisons politiques, mais aussi des raisons plus sentimentales (Cleopatre ?). Il tente d'abord d'obtenir le remboursement de dettes que Ptolemee XII"), (-46,"Les deux souverains sont convoques par Cesar au palais royal d'Alexandrie. Ptolemee-XIII s'y rend après diverses tergiversations ainsi que Cleopatre."), (-47,"A Rome, Cleopatre epouse alors un autre de ses frères cadets, à Alexandrie, Ptolemee-XIV, sur l'injonction de Jules Cesar"), (-46,"Cesar a-t-il comme objectif de montrer ce qu'il en coûte de se revolter contre Rome en faisant figurer dans son triomphe la sœur de Cleopatre et de Ptolemee-XIV, Arsinoe, qui s'est fait reconnaître reine par les troupes de Ptolemee-XIII ?"), (-44,"Au debut de l'annee -44, Cesar est assassine par Brutus. Profitant de la situation confuse qui s'ensuit, Cleopatre quitte alors Rome à la mi-avril, faisant escale en Grèce. Elle parvient à Alexandrie en juillet -44."), (-44,"La guerre que se livrent les assassins de Cesar, Cassius et Brutus et ses heritiers, Octave et Marc-Antoine, oblige Cleopatre à des contorsions diplomatiques."), (-41,"Nous ignorons depuis quand Cleopatre, agee de 29 ans en -41, et Marc-Antoine, qui a une quarantaine d'annees, se connaissent. Marc-Antoine est l'un des officiers qui ont participe au retablissement de Ptolemee XII. Il est plus vraisemblable qu'ils se soient frequentes lors du sejour à Rome de Cleopatre."), (-42,"Brutus tient la Grèce tandis que Cassius s'installe en Syrie. Le gouverneur de Cleopatre à Chypre, Serapion, vient en aide à Cassius."), (-42,"Cassius aurait envisage de s'emparer d'Alexandrie quand le 'debarquement' en Grèce d'Antoine et d'Octave l'oblige à renoncer à ses projets")]