]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo/Example.hs
Strating to add PhyloView and PhyloQuery
[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, member, adjust, singleton, empty, (!), keys, restrictKeys, mapWithKey, filterWithKey, mapKeys, intersectionWith, unionWith)
36 import Data.Maybe (mapMaybe)
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 Gargantext.Prelude hiding (head)
45 import Gargantext.Text.Terms.Mono (monoTexts)
46
47 import Gargantext.Viz.Phylo
48 import Gargantext.Viz.Phylo.Aggregates.Cluster
49 import Gargantext.Viz.Phylo.Aggregates.Cooc
50 import Gargantext.Viz.Phylo.Aggregates.Document
51 import Gargantext.Viz.Phylo.Aggregates.Fis
52 import Gargantext.Viz.Phylo.BranchMaker
53 import Gargantext.Viz.Phylo.LevelMaker
54 import Gargantext.Viz.Phylo.LinkMaker
55 import Gargantext.Viz.Phylo.Metrics.Proximity
56 import Gargantext.Viz.Phylo.Metrics.Clustering
57 import Gargantext.Viz.Phylo.Tools
58
59
60 import qualified Data.Bool as Bool
61 import qualified Data.List as List
62 import qualified Data.Map as Map
63 import qualified Data.Maybe as Maybe
64 import qualified Data.Set as Set
65 import qualified Data.Tuple as Tuple
66 import qualified Data.Vector as Vector
67
68
69 ------------------------------------------------------------------------
70 -- | STEP 12 | -- Return a Phylo for upcomming visiualization tasks
71
72
73 -- -- | To get all the single PhyloPeriodIds covered by a PhyloBranch
74 -- getBranchPeriods :: PhyloBranch -> [PhyloPeriodId]
75 -- getBranchPeriods b = nub $ map (fst . fst) $ getBranchGroupIds b
76
77
78 -- -- | To get all the single PhyloPeriodIds covered by a PhyloBranch
79 -- getBranchGroupIds :: PhyloBranch -> [PhyloGroupId]
80 -- getBranchGroupIds =_phylo_branchGroups
81
82
83 -- | To transform a list of Ngrams Indexes into a Label
84 ngramsToLabel :: Vector Ngrams -> [Int] -> Text
85 ngramsToLabel ngrams l = unwords $ ngramsToText ngrams l
86
87
88 -- | To transform a list of Ngrams Indexes into a list of Text
89 ngramsToText :: Vector Ngrams -> [Int] -> [Text]
90 ngramsToText ngrams l = map (\idx -> ngrams Vector.! idx) l
91
92
93 -- | To get the nth most frequent Ngrams in a list of PhyloGroups
94 mostFreqNgrams :: Int -> [PhyloGroup] -> [Int]
95 mostFreqNgrams thr groups = map fst
96 $ take thr
97 $ reverse
98 $ sortOn snd
99 $ map (\g -> (head g,length g))
100 $ groupBy (==)
101 $ (sort . concat)
102 $ map getGroupNgrams groups
103
104
105 -- | To get the (nth `div` 2) most cooccuring Ngrams in a PhyloGroup
106 mostOccNgrams :: Int -> PhyloGroup -> [Int]
107 mostOccNgrams thr group = (nub . concat )
108 $ map (\((f,s),d) -> [f,s])
109 $ take (thr `div` 2)
110 $ reverse $ sortOn snd $ Map.toList $ getGroupCooc group
111
112
113 freqToLabel :: Int -> [PhyloGroup] -> Vector Ngrams -> Text
114 freqToLabel thr l ngs = ngramsToLabel ngs $ mostFreqNgrams thr l
115
116
117 -- | To filter a list of Branches by avoiding the lone's one (ie: with just a few phyloGroups in the middle of the whole timeline)
118 -- filterLoneBranches :: Int -> Int -> Int -> [PhyloPeriodId] -> [PhyloBranch] -> [PhyloBranch]
119 -- filterLoneBranches nbPinf nbPsup nbG periods branches = filter (not . isLone) branches
120 -- where
121 -- --------------------------------------
122 -- isLone :: PhyloBranch -> Bool
123 -- isLone b = ((length . getBranchGroupIds) b <= nbG)
124 -- && notElem ((head . getBranchPeriods) b) (take nbPinf periods)
125 -- && notElem ((head . getBranchPeriods) b) (take nbPsup $ reverse periods)
126 -- --------------------------------------
127
128
129
130
131 filterLonelyBranch :: PhyloView -> PhyloView
132 filterLonelyBranch graph = graph
133
134 filterHandler :: QueryFilter -> PhyloView -> PhyloView
135 filterHandler fq graph = case _query_filter fq of
136 LonelyBranchFilter -> filterLonelyBranch graph
137
138
139 getBranchIdsWith :: Level -> Phylo -> [PhyloBranchId]
140 getBranchIdsWith lvl p = sortOn snd
141 $ mapMaybe getGroupBranchId
142 $ getGroupsWithLevel lvl p
143
144 phyloParams :: PhyloParam
145 phyloParams = PhyloParam "v0.1" (Software "Gargantext" "v4") ""
146
147 getPhyloParams :: Phylo -> PhyloParam
148 getPhyloParams p = phyloParams
149
150 initPhyloBranch :: PhyloBranchId -> Text -> PhyloBranch
151 initPhyloBranch id lbl = PhyloBranch id lbl empty
152
153 addPhyloNodes :: Bool -> Bool -> Vector Ngrams -> [PhyloGroup] -> [PhyloNode]
154 addPhyloNodes isR isV ns gs = map (\g -> let idxs = getGroupNgrams g
155 in PhyloNode
156 (getGroupId g) "" idxs
157 (if isV
158 then Just (ngramsToText ns idxs)
159 else Nothing)
160 empty
161 (if isR
162 then Just (head $ getGroupLevelParentsId g)
163 else Nothing)
164 ) $ gs
165
166
167 initPhyloEdge :: PhyloGroup -> [Pointer] -> [PhyloEdge]
168 initPhyloEdge g pts = map (\pt -> PhyloEdge (getGroupId g) (fst pt) (snd pt)) pts
169
170 addPhyloEdgesLevel :: EdgeType -> [PhyloGroup] -> [PhyloEdge]
171 addPhyloEdgesLevel e gs = concat
172 $ map (\g -> case e of
173 Ascendant -> initPhyloEdge g (_phylo_groupLevelParents g)
174 Descendant -> initPhyloEdge g (_phylo_groupLevelChilds g)) gs
175
176 addPhyloEdgesPeriod :: EdgeType -> [PhyloGroup] -> [PhyloEdge]
177 addPhyloEdgesPeriod e gs = concat
178 $ map (\g -> case e of
179 Ascendant -> initPhyloEdge g (_phylo_groupPeriodParents g)
180 Descendant -> initPhyloEdge g (_phylo_groupPeriodChilds g)) gs
181
182
183 addBranches :: Level -> Phylo -> [PhyloBranch]
184 addBranches lvl p = map (\id -> initPhyloBranch id "")
185 $ getBranchIdsWith lvl p
186
187
188 initPhyloView :: Level -> Text -> Text -> EdgeType -> Bool -> Phylo -> PhyloView
189 initPhyloView lvl lbl dsc e vb p = PhyloView (getPhyloParams p) lbl dsc e empty
190 ([] ++ (addBranches lvl p))
191 ([] ++ (addPhyloNodes True vb (getFoundations p) groups))
192 (case e of
193 Complete -> [] ++ (addPhyloEdgesPeriod Ascendant groups) ++ (addPhyloEdgesPeriod Descendant groups)
194 _ -> [] ++ (addPhyloEdgesPeriod e groups))
195 where
196 --------------------------------------
197 groups :: [PhyloGroup]
198 groups = getGroupsWithLevel lvl p
199 --------------------------------------
200
201
202 addChildNodes :: Bool -> Level -> Level -> Bool -> EdgeType -> Phylo -> PhyloView -> PhyloView
203 addChildNodes ok lvl lvl' vb e p v
204 | not ok = v
205 | lvl == lvl' = v
206 | otherwise = addChildNodes ok lvl (lvl' - 1) vb e p
207 $ v & over (phylo_viewBranches) (++ (addBranches (lvl' - 1) p))
208 & over (phylo_viewNodes) (++ (addPhyloNodes False vb (getFoundations p) groups'))
209 & over (phylo_viewEdges) (case e of
210 Complete -> (++ ((addPhyloEdgesPeriod Ascendant groups') ++ (addPhyloEdgesPeriod Descendant groups')))
211 _ -> (++ (addPhyloEdgesPeriod e groups)))
212 & over (phylo_viewEdges) (++ (addPhyloEdgesLevel Descendant groups))
213 & over (phylo_viewEdges) (++ (addPhyloEdgesLevel Ascendant groups'))
214 where
215 --------------------------------------
216 groups :: [PhyloGroup]
217 groups = getGroupsWithLevel lvl' p
218 --------------------------------------
219 groups' :: [PhyloGroup]
220 groups' = getGroupsWithLevel (lvl' - 1) p
221 --------------------------------------
222
223 queryToView :: PhyloQuery -> Phylo -> PhyloView
224 queryToView q p = addChildNodes (_query_childs q) (_query_lvl q) (_query_childsDepth q) (_query_verbose q) (_query_edgeType q) p
225 $ initPhyloView (_query_lvl q) "Phylo2000" "This is a Phylo" (_query_edgeType q) (_query_verbose q) p
226
227
228 defaultQuery :: PhyloQuery
229 defaultQuery = PhyloQuery 3 Descendant False 0 [] [] [] Nothing Flat True
230
231
232 textQuery :: Text
233 textQuery = "level=3&childs=false&filter=LonelyBranchFilter(2,2,1):true&metric=BranchAge&tagger=BranchLabelFreq&tagger=GroupLabelCooc"
234
235 -- | To do : add a queryParser from an URL and then update the defaultQuery
236 urlToQuery :: Text -> PhyloQuery
237 urlToQuery url = defaultQuery
238 & query_lvl .~ 3
239 & query_childs .~ False
240 & over (query_metrics) (++ [BranchAge])
241 & over (query_filters) (++ [QueryFilter LonelyBranchFilter [Qp1 2,Qp1 2,Qp1 1] (== Qp3 True)])
242 & over (query_taggers) (++ [BranchLabelFreq,GroupLabelCooc])
243
244
245 toPhyloView :: Text -> Phylo -> PhyloView
246 toPhyloView url p = queryToView (urlToQuery url) p
247
248
249 ------------------------------------------------------------------------
250 -- | STEP 11 | -- Incrementaly cluster the PhyloGroups n times, link them through the Periods and build level n of the Phylo
251
252
253 phylo6 :: Phylo
254 phylo6 = toNthLevel 6 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) (WeightedLogJaccard,[0.01,0]) phylo3
255
256
257 phylo3 :: Phylo
258 phylo3 = setPhyloBranches 3
259 $ interTempoMatching Childs 3 (WeightedLogJaccard,[0.01,0])
260 $ interTempoMatching Parents 3 (WeightedLogJaccard,[0.01,0])
261 $ setLevelLinks (2,3)
262 $ addPhyloLevel 3
263 (phyloToClusters 2 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) phyloBranch2)
264 phyloBranch2
265
266
267 ------------------------------------------------------------------------
268 -- | STEP 10 | -- Cluster the Fis
269
270 phyloBranch2 :: Phylo
271 phyloBranch2 = setPhyloBranches 2 phylo2_c
272
273
274 phylo2_c :: Phylo
275 phylo2_c = interTempoMatching Childs 2 (WeightedLogJaccard,[0.01,0]) phylo2_p
276
277
278 phylo2_p :: Phylo
279 phylo2_p = interTempoMatching Parents 2 (WeightedLogJaccard,[0.01,0]) phylo2_1_2
280
281
282 phylo2_1_2 :: Phylo
283 phylo2_1_2 = setLevelLinks (1,2) phylo2
284
285
286 -- | phylo2 allready contains the LevelChilds links from 2 to 1
287 phylo2 :: Phylo
288 phylo2 = addPhyloLevel 2 phyloCluster phyloBranch1
289
290
291 phyloCluster :: Map (Date,Date) [Cluster]
292 phyloCluster = phyloToClusters 1 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) phyloBranch1
293
294
295 ------------------------------------------------------------------------
296 -- | STEP 9 | -- Find the Branches
297
298
299 phyloBranch1 :: Phylo
300 phyloBranch1 = setPhyloBranches 1 phylo1_c
301
302
303 ------------------------------------------------------------------------
304 -- | STEP 8 | -- Link the PhyloGroups of level 1 through the Periods
305
306
307 phylo1_c :: Phylo
308 phylo1_c = interTempoMatching Childs 1 (WeightedLogJaccard,[0.01,0]) phylo1_p
309
310
311 phylo1_p :: Phylo
312 phylo1_p = interTempoMatching Parents 1 (WeightedLogJaccard,[0.01,0]) phylo1_0_1
313
314
315 ------------------------------------------------------------------------
316 -- | STEP 7 | -- Build the coocurency Matrix of the Phylo
317
318
319 phyloCooc :: Map (Int, Int) Double
320 phyloCooc = fisToCooc phyloFis phylo1_0_1
321
322
323 ------------------------------------------------------------------------
324 -- | STEP 6 | -- Build the level 1 of the Phylo
325
326
327 phylo1_0_1 :: Phylo
328 phylo1_0_1 = setLevelLinks (0,1) phylo1_1_0
329
330
331 phylo1_1_0 :: Phylo
332 phylo1_1_0 = setLevelLinks (1,0) phylo1
333
334
335 phylo1 :: Phylo
336 phylo1 = addPhyloLevel (1) phyloFis phylo
337
338
339 ------------------------------------------------------------------------
340 -- | STEP 5 | -- Create lists of Frequent Items Set and filter them
341
342
343 phyloFis :: Map (Date, Date) [Fis]
344 phyloFis = filterFisBySupport False 1 (filterFisByNested (docsToFis phyloDocs))
345
346
347 ------------------------------------------------------------------------
348 -- | STEP 2 | -- Init a Phylo of level 0
349
350
351 -- phylo' :: Phylo
352 -- phylo' = initPhylo 5 3 corpus actants groupNgramsWithTrees
353
354
355 phylo :: Phylo
356 phylo = addPhyloLevel 0 phyloDocs phyloBase
357
358
359 phyloDocs :: Map (Date, Date) [Document]
360 phyloDocs = corpusToDocs groupNgramsWithTrees corpus phyloBase
361
362
363 ------------------------------------------------------------------------
364 -- | STEP 1 | -- Init the Base of the Phylo from Periods and Foundations
365
366
367 phyloBase :: Phylo
368 phyloBase = initPhyloBase periods foundations
369
370
371 periods :: [(Date,Date)]
372 periods = initPeriods 5 3
373 $ both fst (head corpus,last corpus)
374
375
376 foundations :: Vector Ngrams
377 foundations = initFoundations actants
378
379
380 ------------------------------------------------------------------------
381 -- | STEP 0 | -- Let's start with an example
382
383
384 actants :: [Ngrams]
385 actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV"
386 , "Marc-Antoine", "Cesar" , "Antoine" , "Octave" , "Rome"
387 , "Alexandrie" , "Auguste" , "Pompee" , "Cassius" , "Brutus"]
388
389
390 corpus :: [(Date, Text)]
391 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")]