]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo/Example.hs
add the foundations to the phylo
[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.Semigroup (Semigroup)
37 import Data.Set (Set)
38 import Data.Text (Text, unwords, toLower, words)
39 import Data.Tuple (fst, snd)
40 import Data.Tuple.Extra
41 import Data.Vector (Vector, fromList, elemIndex, (!))
42
43 import Gargantext.Prelude hiding (head)
44 import Gargantext.Text.Terms.Mono (monoTexts)
45
46 import Gargantext.Viz.Phylo
47 import Gargantext.Viz.Phylo.Aggregates.Cluster
48 import Gargantext.Viz.Phylo.Aggregates.Cooc
49 import Gargantext.Viz.Phylo.Aggregates.Document
50 import Gargantext.Viz.Phylo.Aggregates.Fis
51 import Gargantext.Viz.Phylo.BranchMaker
52 import Gargantext.Viz.Phylo.LevelMaker
53 import Gargantext.Viz.Phylo.LinkMaker
54 import Gargantext.Viz.Phylo.Metrics.Proximity
55 import Gargantext.Viz.Phylo.Metrics.Clustering
56 import Gargantext.Viz.Phylo.Tools
57
58
59 import qualified Data.Bool as Bool
60 import qualified Data.List as List
61 import qualified Data.Map as Map
62 import qualified Data.Maybe as Maybe
63 import qualified Data.Set as Set
64 import qualified Data.Tuple as Tuple
65 import qualified Data.Vector as Vector
66
67
68 ------------------------------------------------------------------------
69 -- | STEP 12 | -- Return a Phylo for upcomming visiualization tasks
70
71
72 -- | To get all the single PhyloPeriodIds covered by a PhyloBranch
73 getBranchPeriods :: PhyloBranch -> [PhyloPeriodId]
74 getBranchPeriods b = nub $ map (fst . fst) $ getBranchGroupIds b
75
76
77 -- | To get all the single PhyloPeriodIds covered by a PhyloBranch
78 getBranchGroupIds :: PhyloBranch -> [PhyloGroupId]
79 getBranchGroupIds =_phylo_branchGroups
80
81
82 -- | To transform a list of Ngrams Indexes into a Label
83 ngramsToLabel :: Vector Ngrams -> [Int] -> Text
84 ngramsToLabel ngrams l = unwords $ ngramsToText ngrams l
85
86
87 -- | To transform a list of Ngrams Indexes into a list of Text
88 ngramsToText :: Vector Ngrams -> [Int] -> [Text]
89 ngramsToText ngrams l = map (\idx -> ngrams Vector.! idx) l
90
91
92 -- | To get the nth most frequent Ngrams in a list of PhyloGroups
93 mostFreqNgrams :: Int -> [PhyloGroup] -> [Int]
94 mostFreqNgrams thr groups = map fst
95 $ take thr
96 $ reverse
97 $ sortOn snd
98 $ map (\g -> (head g,length g))
99 $ groupBy (==)
100 $ (sort . concat)
101 $ map getGroupNgrams groups
102
103
104 -- | To get the (nth `div` 2) most cooccuring Ngrams in a PhyloGroup
105 mostOccNgrams :: Int -> PhyloGroup -> [Int]
106 mostOccNgrams thr group = (nub . concat )
107 $ map (\((f,s),d) -> [f,s])
108 $ take (thr `div` 2)
109 $ reverse $ sortOn snd $ Map.toList $ getGroupCooc group
110
111
112 freqToLabel :: Int -> [PhyloGroup] -> Vector Ngrams -> Text
113 freqToLabel thr l ngs = ngramsToLabel ngs $ mostFreqNgrams thr l
114
115
116 -- | 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)
117 filterLoneBranches :: Int -> Int -> Int -> [PhyloPeriodId] -> [PhyloBranch] -> [PhyloBranch]
118 filterLoneBranches nbPinf nbPsup nbG periods branches = filter (not . isLone) branches
119 where
120 --------------------------------------
121 isLone :: PhyloBranch -> Bool
122 isLone b = ((length . getBranchGroupIds) b <= nbG)
123 && notElem ((head . getBranchPeriods) b) (take nbPinf periods)
124 && notElem ((head . getBranchPeriods) b) (take nbPsup $ reverse periods)
125 --------------------------------------
126
127 -- alterBranchLabel :: (Int -> [PhyloGroup] -> Vector Ngrams -> Text) -> PhyloBranch -> Phylo -> PhyloBranch
128 -- alterBranchLabel f b p = over (phylo_branchLabel) (\lbl -> f 2 (getGroupsFromIds (getBranchGroupIds b) p) (getVector Ngrams p)) b
129
130 -- toPhyloView1 :: Level -> Phylo -> [PhyloBranch]
131 -- toPhyloView1 lvl p = bs
132 -- where
133 -- bs = map (\b -> alterBranchLabel freqToLabel b p)
134 -- $ filterLoneBranches 1 1 1 (getPhyloPeriods p)
135 -- $ filter (\b -> (fst . _phylo_branchId) b == lvl)
136 -- $ getPhyloBranches p
137
138 -- view1 = toPhyloView1 2 phylo3
139
140 ------------------------------------------------------------------------
141 -- | STEP 11 | -- Incrementaly cluster the PhyloGroups n times, link them through the Periods and build level n of the Phylo
142
143
144 phylo6 :: Phylo
145 phylo6 = toNthLevel 6 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) (WeightedLogJaccard,[0.01,0]) phylo3
146
147
148 phylo3 :: Phylo
149 phylo3 = pairGroupsToGroups Childs 3 (WeightedLogJaccard,[0.01,0])
150 $ pairGroupsToGroups Parents 3 (WeightedLogJaccard,[0.01,0])
151 $ setLevelLinks (2,3)
152 $ addPhyloLevel 3
153 (phyloToClusters 2 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) phyloBranch2)
154 phyloBranch2
155
156
157 ------------------------------------------------------------------------
158 -- | STEP 10 | -- Cluster the Fis
159
160 phyloBranch2 :: Phylo
161 phyloBranch2 = phylo2_c
162 -- phyloBranch2 = setPhyloBranches 2 phylo2_c
163
164
165 phylo2_c :: Phylo
166 phylo2_c = pairGroupsToGroups Childs 2 (WeightedLogJaccard,[0.01,0]) phylo2_p
167
168
169 phylo2_p :: Phylo
170 phylo2_p = pairGroupsToGroups Parents 2 (WeightedLogJaccard,[0.01,0]) phylo2_1_2
171
172
173 phylo2_1_2 :: Phylo
174 phylo2_1_2 = setLevelLinks (1,2) phylo2
175
176
177 -- | phylo2 allready contains the LevelChilds links from 2 to 1
178 phylo2 :: Phylo
179 phylo2 = addPhyloLevel 2 phyloCluster phyloBranch1
180
181
182 phyloCluster :: Map (Date,Date) [Cluster]
183 phyloCluster = phyloToClusters 1 (WeightedLogJaccard,[0.01,0]) (RelatedComponents, []) phyloBranch1
184
185
186 ------------------------------------------------------------------------
187 -- | STEP 9 | -- Find the Branches
188
189
190 phyloBranch1 = phylo1_c
191
192 -- phyloBranch1 :: Phylo
193 -- phyloBranch1 = setPhyloBranches 1 phylo1_c
194
195
196 ------------------------------------------------------------------------
197 -- | STEP 8 | -- Link the PhyloGroups of level 1 through the Periods
198
199
200 phylo1_c :: Phylo
201 phylo1_c = pairGroupsToGroups Childs 1 (WeightedLogJaccard,[0.01,0]) phylo1_p
202
203
204 phylo1_p :: Phylo
205 phylo1_p = pairGroupsToGroups Parents 1 (WeightedLogJaccard,[0.01,0]) phylo1_0_1
206
207
208 ------------------------------------------------------------------------
209 -- | STEP 7 | -- Build the coocurency Matrix of the Phylo
210
211
212 phyloCooc :: Map (Int, Int) Double
213 phyloCooc = fisToCooc phyloFis phylo1_0_1
214
215
216 ------------------------------------------------------------------------
217 -- | STEP 6 | -- Build the level 1 of the Phylo
218
219
220 phylo1_0_1 :: Phylo
221 phylo1_0_1 = setLevelLinks (0,1) phylo1_1_0
222
223
224 phylo1_1_0 :: Phylo
225 phylo1_1_0 = setLevelLinks (1,0) phylo1
226
227
228 phylo1 :: Phylo
229 phylo1 = addPhyloLevel (1) phyloFis phylo
230
231
232 ------------------------------------------------------------------------
233 -- | STEP 5 | -- Create lists of Frequent Items Set and filter them
234
235
236 phyloFis :: Map (Date, Date) [Fis]
237 phyloFis = filterFisBySupport False 1 (filterFisByNested (docsToFis phyloDocs))
238
239
240 ------------------------------------------------------------------------
241 -- | STEP 2 | -- Init a Phylo of level 0
242
243
244 -- phylo' :: Phylo
245 -- phylo' = initPhylo 5 3 corpus actants groupNgramsWithTrees
246
247
248 phylo :: Phylo
249 phylo = addPhyloLevel 0 phyloDocs phyloBase
250
251
252 phyloDocs :: Map (Date, Date) [Document]
253 phyloDocs = corpusToDocs groupNgramsWithTrees corpus phyloBase
254
255
256 ------------------------------------------------------------------------
257 -- | STEP 1 | -- Init the Base of the Phylo from Periods and Foundations
258
259
260 phyloBase :: Phylo
261 phyloBase = initPhyloBase periods foundations
262
263
264 periods :: [(Date,Date)]
265 periods = initPeriods 5 3
266 $ both fst (head corpus,last corpus)
267
268
269 foundations :: Vector Ngrams
270 foundations = initFoundations actants
271
272
273 ------------------------------------------------------------------------
274 -- | STEP 0 | -- Let's start with an example
275
276
277 actants :: [Ngrams]
278 actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV"
279 , "Marc-Antoine", "Cesar" , "Antoine" , "Octave" , "Rome"
280 , "Alexandrie" , "Auguste" , "Pompee" , "Cassius" , "Brutus"]
281
282
283 corpus :: [(Date, Text)]
284 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")]