]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo/Example.hs
Refactor links 0 to -1 and -1 to 0 with lenses
[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
28 module Gargantext.Viz.Phylo.Example where
29
30 import Control.Lens hiding (both)
31 import qualified Data.List as List
32 import Data.Text (Text, unwords, toLower, words)
33 import Data.Tuple.Extra
34 import Data.Semigroup (Semigroup)
35 import Data.Map (Map)
36 import qualified Data.Map as Map
37 import qualified Data.Vector as Vector
38 import qualified Data.Maybe as Maybe
39 import qualified Data.Tuple as Tuple
40
41 import Data.Set (Set)
42 import qualified Data.Set as DS
43 import qualified Data.Matrix as DM'
44
45 import Gargantext.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
46 import Gargantext.Text.Terms.Mono (monoTexts)
47 import Gargantext.Prelude
48 import Gargantext.Viz.Phylo
49
50 ------------------------------------------------------------------------
51 -- | Types | --
52
53
54 -- | Date : a simple Integer
55 type Date = Int
56 -- | Document : a piece of Text linked to a Date
57 data Document = Document
58 { date :: Date
59 , text :: Text
60 } deriving (Show)
61 -- | Corpus : a list of Documents
62 type Corpus = [Document]
63
64
65 type MapList = [Ngrams]
66 type PeriodeSize = Int
67 -- data Periodes b a = Map (b,b) a
68 type Occurrences = Int
69
70 data Levels = Level_m1 | Level_0 | Level_1 | Level_2 | Level_N
71 deriving (Show, Eq, Enum, Bounded)
72
73
74
75
76 data LinkLvlLabel = Link_m1_0 | Link_0_m1 | Link_1_0 | Link_x_y
77 deriving (Show, Eq, Enum, Bounded)
78
79 data LinkLvl = LinkLvl
80 { linkLvlLabel :: LinkLvlLabel
81 , linkLvlFrom :: Int
82 , linkLvlTo :: Int
83 } deriving (Show)
84
85
86 data PhyloError = LevelDoesNotExist
87 | LevelUnassigned
88 deriving (Show)
89
90
91 --------------------------------------------------------------------
92 phyloExampleFinal :: Phylo
93 phyloExampleFinal = undefined
94
95 --------------------------------------------------------------------
96 appariement :: Map (Date, Date) (Map (Set Ngrams) Int)
97 appariement = undefined
98
99 ------------------------------------------------------------------------
100 -- | STEP 10 | -- Incrementaly cluster the PhyloGroups n times, link them through the Periods and build level n of the Phylo
101
102
103 ------------------------------------------------------------------------
104 -- | STEP 9 | -- Link the PhyloGroups of level 1 through the Periods
105
106
107 ------------------------------------------------------------------------
108 -- | STEP 8 | -- Cluster the Fis and buil level 1 of the Phylo
109
110
111 ------------------------------------------------------------------------
112 -- | STEP 7 | -- Find the Fis out of Documents and Ngrams and build level 1 of the Phylo
113
114
115 phyloFis :: Map (Date, Date) Fis
116 phyloFis = termsToFis phyloTerms
117
118 termsToFis :: Map (Date, Date) [Document]
119 -> Map (Date, Date) Fis
120 termsToFis = corpusToFis (words . text)
121
122 -- | TODO: parameters has to be checked
123 -- | TODO FIS on monotexts
124 corpusToFis :: (Document -> [Ngrams])
125 -> Map (Date, Date) [Document]
126 -> Map (Date, Date) (Map (Set Ngrams) Int)
127 corpusToFis f = Map.map (\d -> fisWithSizePolyMap (Segment 1 20) 1 (map f d))
128
129 ------------------------------------------------------------------------
130 -- | STEP 7 | -- Link level -1 to level 0
131
132 phyloLinked_m1_0 :: Phylo
133 phyloLinked_m1_0 = phyloToLinks lvl_m1_0 phyloLinked_0_m1
134
135 lvl_m1_0 :: LinkLvl
136 lvl_m1_0 = (LinkLvl Link_m1_0 (-1) 0)
137
138 ------------------------------------------------------------------------
139 -- | STEP 6 | -- Link level 0 to level -1
140
141
142 addPointer :: Semigroup field
143 => ASetter current target identity (field -> field)
144 -> field -> current -> target
145 addPointer field targetPointer current =
146 set field (<> targetPointer) current
147
148 getGroups :: Phylo -> [PhyloGroup]
149 getGroups = view (phylo_periods . traverse . phylo_periodLevels . traverse . phylo_levelGroups)
150
151 getGroupId :: PhyloGroup -> PhyloGroupId
152 getGroupId = view (phylo_groupId)
153
154 getGroupLvl :: PhyloGroup -> Int
155 getGroupLvl group = Tuple.snd $ Tuple.fst $ getGroupId group
156
157 getGroupPeriod :: PhyloGroup -> (Date,Date)
158 getGroupPeriod group = Tuple.fst $ Tuple.fst $ getGroupId group
159
160 getGroupsByLevelAndPeriod :: Int -> (Date,Date) -> Phylo -> [PhyloGroup]
161 getGroupsByLevelAndPeriod lvl period p = List.filter (\group -> (getGroupLvl group == lvl) && (getGroupPeriod group == period)) (getGroups p)
162
163 containsIdx :: [Int] -> [Int] -> Bool
164 containsIdx l l'
165 | List.null l' = False
166 | List.last l < List.head l' = False
167 | List.head l' `List.elem` l = True
168 | otherwise = containsIdx l (List.tail l')
169
170 shouldLink :: LinkLvl -> [Int] -> [Int] -> Bool
171 shouldLink lvl current target = case linkLvlLabel lvl of
172 Link_0_m1 -> containsIdx target current
173 Link_m1_0 -> containsIdx target current
174 Link_x_y -> undefined
175 _ -> panic ("error link level to be defined")
176
177 linkGroupToGroups :: LinkLvl -> PhyloGroup -> [PhyloGroup] -> PhyloGroup
178 linkGroupToGroups lvl current targets
179 | linkLvlFrom lvl < linkLvlTo lvl = setLevelParents current
180 | linkLvlFrom lvl > linkLvlTo lvl = setLevelChilds current
181 | otherwise = current
182 where
183 setLevelChilds :: PhyloGroup -> PhyloGroup
184 setLevelChilds = over (phylo_groupLevelChilds) addPointers
185
186 setLevelParents :: PhyloGroup -> PhyloGroup
187 setLevelParents = over (phylo_groupLevelParents) addPointers
188
189 addPointers :: [Pointer] -> [Pointer]
190 addPointers lp = lp List.++ Maybe.mapMaybe (\target -> if shouldLink lvl (_phylo_groupNgrams current) (_phylo_groupNgrams target)
191 then Just ((getGroupId target),1)
192 else Nothing
193 ) targets
194
195 addPointers' :: [Pointer] -> [Pointer]
196 addPointers' lp = lp List.++ map (\target -> ((getGroupId target),1)) targets
197
198 linkGroupsByLevel :: LinkLvl -> Phylo -> [PhyloGroup] -> [PhyloGroup]
199 linkGroupsByLevel lvl p groups = map (\group ->
200 if getGroupLvl group == linkLvlFrom lvl
201 then linkGroupToGroups lvl group (getGroupsByLevelAndPeriod (linkLvlTo lvl) (getGroupPeriod group) p)
202 else group ) groups
203
204 phyloToLinks :: LinkLvl -> Phylo -> Phylo
205 phyloToLinks lvl p = over (phylo_periods . traverse . phylo_periodLevels . traverse . phylo_levelGroups) (\groups -> linkGroupsByLevel lvl p groups) p
206
207 phyloLinked_0_m1 :: Phylo
208 phyloLinked_0_m1 = phyloToLinks lvl_0_m1 phyloWithGroups0
209
210 lvl_0_m1 :: LinkLvl
211 lvl_0_m1 = (LinkLvl Link_0_m1 0 (-1))
212
213 ------------------------------------------------------------------------
214 -- | STEP 5 | -- Build level 0 (for the moment it's just a durty copy of level -1)
215
216
217 setGroupIdLvl :: Int -> PhyloGroup -> PhyloGroup
218 setGroupIdLvl lvl (PhyloGroup ((period, lvl'), idx) gLabel gNgrams gPP gPC gLP gLC)
219 = PhyloGroup ((period, lvl), idx) gLabel gNgrams gPP gPC gLP gLC
220
221 setPhyloLevel :: Int -> PhyloLevel -> PhyloLevel
222 setPhyloLevel lvl (PhyloLevel (periodId, lvl') lvlGroups)
223 = PhyloLevel (periodId, lvl) lvlGroups'
224 where
225 lvlGroups' = map (\g -> setGroupIdLvl lvl g) lvlGroups
226
227 copyPhyloLevel :: Int -> [PhyloLevel] -> [PhyloLevel]
228 copyPhyloLevel lvl l = (setPhyloLevel lvl (List.head l)) : l
229
230 alterLvl :: Int -> [PhyloPeriod] -> [PhyloPeriod]
231 alterLvl lvl l = map (\p -> PhyloPeriod (_phylo_periodId p) (copyPhyloLevel lvl $ _phylo_periodLevels p)) l
232
233 phyloWithGroups0 :: Phylo
234 phyloWithGroups0 = updatePhyloByLevel Level_0 phyloWithGroupsm1
235
236
237 ------------------------------------------------------------------------
238 -- | STEP 4 | -- Build level -1
239
240
241 findIdx :: Ngrams -> Int
242 findIdx n = case (Vector.elemIndex n (_phylo_ngrams phylo)) of
243 Nothing -> panic "PhyloError"
244 Just i -> i
245
246 ngramsToGroup :: [Ngrams] -> Text -> Int -> Int -> Int -> Int -> PhyloGroup
247 ngramsToGroup terms label idx lvl from to = PhyloGroup (((from, to), lvl), idx) label (List.sort (map (\x -> findIdx x) terms)) [] [] [] []
248
249 docsToLevel :: (Date, Date) -> Corpus -> PhyloLevel
250 docsToLevel k v = PhyloLevel (k,(-1)) (map (\x ->
251 ngramsToGroup [Tuple.snd x] (Tuple.snd x) (Tuple.fst x) (-1) (Tuple.fst k) (Tuple.snd k)
252 ) $ zip [1..] $ (List.nub . List.concat) $ map (words . text) v)
253
254 corpusToPhyloPeriod :: Map (Date,Date) Corpus -> [PhyloPeriod]
255 corpusToPhyloPeriod corpus = map (\x -> PhyloPeriod (Tuple.fst x) [(Tuple.snd x)]) $ zip (Map.keys mapLvl) (Map.elems mapLvl)
256 where
257 mapLvl :: Map (Date,Date) PhyloLevel
258 mapLvl = Map.mapWithKey docsToLevel corpus
259
260 updatePhyloByLevel :: Levels -> Phylo -> Phylo
261 updatePhyloByLevel lvl (Phylo pDuration pNgrams pPeriods)
262 = case lvl of
263
264 Level_m1 -> Phylo pDuration pNgrams pPeriods'
265 where pPeriods' = (corpusToPhyloPeriod phyloTerms) List.++ pPeriods
266
267 Level_0 -> Phylo pDuration pNgrams pPeriods'
268 where pPeriods' = alterLvl 0 pPeriods
269
270 _ -> panic ("error level to be defined")
271
272 phyloWithGroupsm1 :: Phylo
273 phyloWithGroupsm1 = updatePhyloByLevel Level_m1 phylo
274
275
276 ------------------------------------------------------------------------
277 -- | STEP 3 | -- Split the Corpus into Periods and reduce each Document as a list of Ngrams
278
279
280 phyloTerms :: Map (Date, Date) [Document]
281 phyloTerms = toPeriodes date 5 3 $ cleanCorpus cleanedActants phyloCorpus
282
283 toPeriodes :: (Ord date, Enum date) => (doc -> date)
284 -> Grain -> Step -> [doc] -> Map (date, date) [doc]
285 toPeriodes _ _ _ [] = panic "Empty corpus can not have any periods"
286 toPeriodes f g s es = Map.fromList $ zip hs $ map (inPeriode f es) hs
287 where
288 hs = steps g s $ both f (List.head es, List.last es)
289 --------------------------------------------------------------------
290 -- | Define overlapping periods of time by following regular steps
291 inPeriode :: Ord b => (t -> b) -> [t] -> (b, b) -> [t]
292 inPeriode f' h (start,end) =
293 fst $ List.partition (\d -> f' d >= start && f' d <= end) h
294 --------------------------------------------------------------------
295 -- | Find steps of linear and homogenous time of integer
296 steps :: (Eq date, Enum date) => Grain -> Step -> (date, date) -> [(date, date)]
297 steps s' o' (start,end) = map (\l -> (List.head l, List.last l))
298 $ chunkAlong s' o' [start .. end]
299
300 cleanCorpus :: MapList -> Corpus -> Corpus
301 cleanCorpus ml = map (\(Document d t) -> Document d (unwords $ filter (\x -> elem x ml) $ monoTexts t))
302
303
304 ------------------------------------------------------------------------
305 -- | STEP 2 | -- Find some Ngrams (ie: phyloGroup of level -1) out of the Corpus & init the phylo
306
307
308 phylo = Phylo (both date $ (List.last &&& List.head) phyloCorpus) phyloNgrams []
309
310 phyloNgrams :: PhyloNgrams
311 phyloNgrams = Vector.fromList cleanedActants
312
313 cleanedActants :: [Ngrams]
314 cleanedActants = map toLower actants
315
316 actants :: [Ngrams]
317 actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV"
318 , "Marc-Antoine", "Cesar" , "Antoine" , "Octave" , "Rome"
319 , "Alexandrie" , "Auguste" , "Pompee" , "Cassius" , "Brutus"]
320
321
322 ------------------------------------------------------------------------
323 -- | STEP 1 | -- Get a corpus of Documents
324
325
326 phyloCorpus :: Corpus
327 phyloCorpus = map (\(d,t) -> Document d t) exampleDocuments
328
329 exampleDocuments :: [(Date, Text)]
330 exampleDocuments = 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")]
331