Commit 1a96a74d authored by Quentin Lobbé's avatar Quentin Lobbé

add the phylopeaks and correct some bugs on the phylodocs

parent e0d27666
Pipeline #328 failed with stage
...@@ -75,17 +75,22 @@ data Software = ...@@ -75,17 +75,22 @@ data Software =
data Phylo = data Phylo =
Phylo { _phylo_duration :: (Start, End) Phylo { _phylo_duration :: (Start, End)
, _phylo_foundations :: Vector Ngrams , _phylo_foundations :: Vector Ngrams
-- , _phylo_peaks :: PhyloPeaks , _phylo_foundationsPeaks :: PhyloPeaks
, _phylo_periods :: [PhyloPeriod] , _phylo_periods :: [PhyloPeriod]
, _phylo_param :: PhyloParam , _phylo_param :: PhyloParam
} }
deriving (Generic, Show) deriving (Generic, Show)
-- data PhyloPeaks = -- | The PhyloPeaks describe the aggregation of some foundations Ngrams behind a list of Ngrams trees (ie: a forest)
-- PhyloPeaks { _phylo_peaksLabel :: Vector Ngrams -- PeaksLabels are the root labels of each Ngrams trees
-- , _phylo_peaksTrees :: [(Ngrams, TreeNgrams)] data PhyloPeaks =
-- } PhyloPeaks { _phylo_peaksLabels :: Vector Ngrams
-- deriving (Generic, Show) , _phylo_peaksForest :: [Tree Ngrams]
}
deriving (Generic, Show)
-- | A Tree of Ngrams where each node is a label
data Tree a = Empty | Node a [Tree a] deriving (Show)
-- | Date : a simple Integer -- | Date : a simple Integer
...@@ -188,9 +193,8 @@ type Ngrams = Text ...@@ -188,9 +193,8 @@ type Ngrams = Text
-- | Document : a piece of Text linked to a Date -- | Document : a piece of Text linked to a Date
data Document = Document data Document = Document
{ date :: Date { date :: Date
, text :: Text , text :: [Ngrams]
} deriving (Show) } deriving (Show)
-- | Clique : Set of ngrams cooccurring in the same Document -- | Clique : Set of ngrams cooccurring in the same Document
type Clique = Set Ngrams type Clique = Set Ngrams
...@@ -430,6 +434,7 @@ makeLenses ''PhyloParam ...@@ -430,6 +434,7 @@ makeLenses ''PhyloParam
makeLenses ''Software makeLenses ''Software
-- --
makeLenses ''Phylo makeLenses ''Phylo
makeLenses ''PhyloPeaks
makeLenses ''PhyloGroup makeLenses ''PhyloGroup
makeLenses ''PhyloLevel makeLenses ''PhyloLevel
makeLenses ''PhyloPeriod makeLenses ''PhyloPeriod
...@@ -452,7 +457,9 @@ makeLenses ''PhyloEdge ...@@ -452,7 +457,9 @@ makeLenses ''PhyloEdge
------------------------ ------------------------
$(deriveJSON (unPrefix "_phylo_" ) ''Phylo ) $(deriveJSON (unPrefix "_phylo_" ) ''Phylo )
$(deriveJSON (unPrefix "_phylo_peaks" ) ''PhyloPeaks )
$(deriveJSON defaultOptions ''Tree )
$(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod ) $(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod )
$(deriveJSON (unPrefix "_phylo_level" ) ''PhyloLevel ) $(deriveJSON (unPrefix "_phylo_level" ) ''PhyloLevel )
$(deriveJSON (unPrefix "_phylo_group" ) ''PhyloGroup ) $(deriveJSON (unPrefix "_phylo_group" ) ''PhyloGroup )
......
...@@ -37,7 +37,7 @@ fisToCooc :: Map (Date, Date) [PhyloFis] -> Phylo -> Map (Int, Int) Double ...@@ -37,7 +37,7 @@ fisToCooc :: Map (Date, Date) [PhyloFis] -> Phylo -> Map (Int, Int) Double
fisToCooc m p = map (/docs) fisToCooc m p = map (/docs)
$ foldl (\mem x -> adjust (+1) (getKeyPair x mem) mem) cooc $ foldl (\mem x -> adjust (+1) (getKeyPair x mem) mem) cooc
$ concat $ concat
$ map (\x -> listToUnDirectedCombiWith (\x -> getIdxInFoundations x p) $ (Set.toList . fst) x) $ map (\x -> listToUnDirectedCombiWith (\x -> getIdxInPeaks x p) $ (Set.toList . fst) x)
$ (concat . elems) m $ (concat . elems) m
where where
-------------------------------------- --------------------------------------
...@@ -48,7 +48,7 @@ fisToCooc m p = map (/docs) ...@@ -48,7 +48,7 @@ fisToCooc m p = map (/docs)
docs = fromIntegral $ foldl (\mem x -> mem + (snd x)) 0 $ (concat . elems) m docs = fromIntegral $ foldl (\mem x -> mem + (snd x)) 0 $ (concat . elems) m
-------------------------------------- --------------------------------------
cooc :: Map (Int, Int) (Double) cooc :: Map (Int, Int) (Double)
cooc = Map.fromList $ map (\x -> (x,0)) (listToUnDirectedCombiWith (\x -> getIdxInFoundations x p) fisNgrams) cooc = Map.fromList $ map (\x -> (x,0)) (listToUnDirectedCombiWith (\x -> getIdxInPeaks x p) fisNgrams)
-------------------------------------- --------------------------------------
......
...@@ -17,8 +17,10 @@ Portability : POSIX ...@@ -17,8 +17,10 @@ Portability : POSIX
module Gargantext.Viz.Phylo.Aggregates.Document module Gargantext.Viz.Phylo.Aggregates.Document
where where
import Data.List (last,head) import Control.Lens hiding (both, Level)
import Data.Map (Map)
import Data.List (last,head,nub,(++))
import Data.Map (Map,member)
import Data.Text (Text, unwords, toLower, words) import Data.Text (Text, unwords, toLower, words)
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Extra import Data.Tuple.Extra
...@@ -37,12 +39,7 @@ import qualified Data.Vector as Vector ...@@ -37,12 +39,7 @@ import qualified Data.Vector as Vector
-- | To init a list of Periods framed by a starting Date and an ending Date -- | To init a list of Periods framed by a starting Date and an ending Date
initPeriods :: (Eq date, Enum date) => Grain -> Step -> (date, date) -> [(date, date)] initPeriods :: (Eq date, Enum date) => Grain -> Step -> (date, date) -> [(date, date)]
initPeriods g s (start,end) = map (\l -> (head l, last l)) initPeriods g s (start,end) = map (\l -> (head l, last l))
$ chunkAlong g s [start .. end] $ chunkAlong g s [start .. end]
-- | To be defined, for the moment it's just the id function
groupNgramsWithTrees :: Ngrams -> Ngrams
groupNgramsWithTrees n = n
-- | To group a list of Documents by fixed periods -- | To group a list of Documents by fixed periods
...@@ -56,23 +53,27 @@ groupDocsByPeriod f pds es = Map.fromList $ zip pds $ map (inPeriode f es) pds ...@@ -56,23 +53,27 @@ groupDocsByPeriod f pds es = Map.fromList $ zip pds $ map (inPeriode f es) pds
fst $ List.partition (\d -> f' d >= start && f' d <= end) h fst $ List.partition (\d -> f' d >= start && f' d <= end) h
-------------------------------------- --------------------------------------
reduceByPeaks :: Map Ngrams Ngrams -> [Ngrams] -> [Ngrams]
reduceByPeaks m ns = (\(f,s) -> f ++ (nub s))
$ foldl (\mem n -> if member n m
then (fst mem,(snd mem) ++ [m Map.! n])
else ((fst mem) ++ [n],snd mem)
) ([],[]) ns
-- | To parse a list of Documents by filtering on a Vector of Ngrams -- | To parse a list of Documents by filtering on a Vector of Ngrams
parseDocs :: (Ngrams -> Ngrams) -> Vector Ngrams -> [Document] -> [Document] parseDocs :: Vector Ngrams -> PhyloPeaks -> [(Date,Text)] -> [Document]
parseDocs f l docs = map (\(Document d t) parseDocs fds peaks c = map (\(d,t)
-> Document d ( unwords -> Document d ( reduceByPeaks mPeaks
-- | To do : change 'f' for the Ngrams Tree Agregation $ filter (\x -> Vector.elem x fds)
$ map f $ monoTexts t)) c
$ filter (\x -> Vector.elem x l) where
$ monoTexts t)) docs --------------------------------------
mPeaks :: Map Ngrams Ngrams
mPeaks = forestToMap (peaks ^. phylo_peaksForest)
--------------------------------------
-- | To transform a Corpus of texts into a Map of aggregated Documents grouped by Periods -- | To transform a Corpus of texts into a Map of aggregated Documents grouped by Periods
corpusToDocs :: (Ngrams -> Ngrams) -> [(Date,Text)] -> Phylo -> Map (Date,Date) [Document] corpusToDocs :: [(Date,Text)] -> Phylo -> Map (Date,Date) [Document]
corpusToDocs f c p = groupDocsByPeriod date (getPhyloPeriods p) corpusToDocs c p = groupDocsByPeriod date (getPhyloPeriods p)
$ parseDocs f (getFoundations p) docs $ parseDocs (getFoundations p) (getPeaks p) c
where \ No newline at end of file
--------------------------------------
docs :: [Document]
docs = map (\(d,t) -> Document d t) c
--------------------------------------
\ No newline at end of file
...@@ -56,4 +56,4 @@ filterFisByNested = map (\l -> let cliqueMax = filterNestedSets (head $ map fst ...@@ -56,4 +56,4 @@ filterFisByNested = map (\l -> let cliqueMax = filterNestedSets (head $ map fst
-- | To transform a list of Documents into a Frequent Items Set -- | To transform a list of Documents into a Frequent Items Set
docsToFis :: Map (Date, Date) [Document] -> Map (Date, Date) [PhyloFis] docsToFis :: Map (Date, Date) [Document] -> Map (Date, Date) [PhyloFis]
docsToFis docs = map (\d -> Map.toList docsToFis docs = map (\d -> Map.toList
$ fisWithSizePolyMap (Segment 1 20) 1 (map (words . text) d)) docs $ fisWithSizePolyMap (Segment 1 20) 1 (map text d)) docs
\ No newline at end of file \ No newline at end of file
...@@ -105,7 +105,7 @@ phyloQueryView = PhyloQueryView 3 Merge False 1 [BranchAge] [defaultSmallBranch] ...@@ -105,7 +105,7 @@ phyloQueryView = PhyloQueryView 3 Merge False 1 [BranchAge] [defaultSmallBranch]
phyloFromQuery :: Phylo phyloFromQuery :: Phylo
phyloFromQuery = toPhylo (queryParser queryEx) corpus actants phyloFromQuery = toPhylo (queryParser queryEx) corpus actants actantsTrees
-- | To do : create a request handler and a query parser -- | To do : create a request handler and a query parser
queryParser :: [Char] -> PhyloQuery queryParser :: [Char] -> PhyloQuery
...@@ -234,7 +234,7 @@ phylo = addPhyloLevel 0 phyloDocs phyloBase ...@@ -234,7 +234,7 @@ phylo = addPhyloLevel 0 phyloDocs phyloBase
phyloDocs :: Map (Date, Date) [Document] phyloDocs :: Map (Date, Date) [Document]
phyloDocs = corpusToDocs groupNgramsWithTrees corpus phyloBase phyloDocs = corpusToDocs corpus phyloBase
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -243,7 +243,7 @@ phyloDocs = corpusToDocs groupNgramsWithTrees corpus phyloBase ...@@ -243,7 +243,7 @@ phyloDocs = corpusToDocs groupNgramsWithTrees corpus phyloBase
phyloBase :: Phylo phyloBase :: Phylo
phyloBase = initPhyloBase periods foundations defaultPhyloParam phyloBase = initPhyloBase periods foundations peaks defaultPhyloParam
periods :: [(Date,Date)] periods :: [(Date,Date)]
...@@ -251,6 +251,10 @@ periods = initPeriods 5 3 ...@@ -251,6 +251,10 @@ periods = initPeriods 5 3
$ both fst (head corpus,last corpus) $ both fst (head corpus,last corpus)
peaks :: PhyloPeaks
peaks = initPeaks (map (\t -> alterLabels phyloAnalyzer t) actantsTrees) foundations
foundations :: Vector Ngrams foundations :: Vector Ngrams
foundations = initFoundations actants foundations = initFoundations actants
...@@ -259,6 +263,9 @@ foundations = initFoundations actants ...@@ -259,6 +263,9 @@ foundations = initFoundations actants
-- | STEP 0 | -- Let's start with an example -- | STEP 0 | -- Let's start with an example
-------------------------------------------- --------------------------------------------
actantsTrees :: [Tree Ngrams]
actantsTrees = [Node "Cite antique" [(Node "Rome" []),(Node "Alexandrie" [])]]
actants :: [Ngrams] actants :: [Ngrams]
actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV" actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV"
...@@ -268,5 +275,3 @@ actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV" ...@@ -268,5 +275,3 @@ actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV"
corpus :: [(Date, Text)] corpus :: [(Date, Text)]
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")] 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")]
...@@ -89,7 +89,7 @@ instance PhyloLevelMaker Document ...@@ -89,7 +89,7 @@ instance PhyloLevelMaker Document
toPhyloGroups lvl (d,d') l m p = map (\(idx,ngram) -> ngramsToGroup (d,d') lvl idx ngram [ngram] p) toPhyloGroups lvl (d,d') l m p = map (\(idx,ngram) -> ngramsToGroup (d,d') lvl idx ngram [ngram] p)
$ zip [1..] $ zip [1..]
$ (nub . concat) $ (nub . concat)
$ map (Text.words . text) l $ map text l
-------------------------------------- --------------------------------------
...@@ -117,7 +117,7 @@ cliqueToGroup prd lvl idx lbl fis m p = ...@@ -117,7 +117,7 @@ cliqueToGroup prd lvl idx lbl fis m p =
where where
-------------------------------------- --------------------------------------
ngrams :: [Int] ngrams :: [Int]
ngrams = sort $ map (\x -> getIdxInFoundations x p) ngrams = sort $ map (\x -> getIdxInPeaks x p)
$ Set.toList $ Set.toList
$ fst fis $ fst fis
-------------------------------------- --------------------------------------
...@@ -130,7 +130,7 @@ cliqueToGroup prd lvl idx lbl fis m p = ...@@ -130,7 +130,7 @@ cliqueToGroup prd lvl idx lbl fis m p =
-- | To transform a list of Ngrams into a PhyloGroup -- | To transform a list of Ngrams into a PhyloGroup
ngramsToGroup :: PhyloPeriodId -> Level -> Int -> Text -> [Ngrams] -> Phylo -> PhyloGroup ngramsToGroup :: PhyloPeriodId -> Level -> Int -> Text -> [Ngrams] -> Phylo -> PhyloGroup
ngramsToGroup prd lvl idx lbl ngrams p = ngramsToGroup prd lvl idx lbl ngrams p =
PhyloGroup ((prd, lvl), idx) lbl (sort $ map (\x -> getIdxInFoundations x p) ngrams) empty empty Nothing [] [] [] [] PhyloGroup ((prd, lvl), idx) lbl (sort $ map (\x -> getIdxInPeaks x p) ngrams) empty empty Nothing [] [] [] []
-- | To traverse a Phylo and add a new PhyloLevel linked to a new list of PhyloGroups -- | To traverse a Phylo and add a new PhyloLevel linked to a new list of PhyloGroups
...@@ -188,9 +188,12 @@ toPhylo0 d p = addPhyloLevel 0 d p ...@@ -188,9 +188,12 @@ toPhylo0 d p = addPhyloLevel 0 d p
-- | To reconstruct the Base of a Phylo -- | To reconstruct the Base of a Phylo
toPhyloBase :: PhyloQuery -> PhyloParam -> [(Date, Text)] -> [Ngrams] -> Phylo toPhyloBase :: PhyloQuery -> PhyloParam -> [(Date, Text)] -> [Ngrams] -> [Tree Ngrams] -> Phylo
toPhyloBase q p c a = initPhyloBase periods foundations p toPhyloBase q p c a ts = initPhyloBase periods foundations peaks p
where where
--------------------------------------
peaks :: PhyloPeaks
peaks = initPeaks (map (\t -> alterLabels phyloAnalyzer t) ts) foundations
-------------------------------------- --------------------------------------
periods :: [(Date,Date)] periods :: [(Date,Date)]
periods = initPeriods (getPeriodGrain q) (getPeriodSteps q) periods = initPeriods (getPeriodGrain q) (getPeriodSteps q)
...@@ -202,8 +205,8 @@ toPhyloBase q p c a = initPhyloBase periods foundations p ...@@ -202,8 +205,8 @@ toPhyloBase q p c a = initPhyloBase periods foundations p
-- | To reconstruct a Phylomemy from a PhyloQuery, a Corpus and a list of actants -- | To reconstruct a Phylomemy from a PhyloQuery, a Corpus and a list of actants
toPhylo :: PhyloQuery -> [(Date, Text)] -> [Ngrams] -> Phylo toPhylo :: PhyloQuery -> [(Date, Text)] -> [Ngrams] -> [Tree Ngrams] -> Phylo
toPhylo q c a = toNthLevel (getNthLevel q) (getInterTemporalMatching q) (getNthCluster q) phylo1 toPhylo q c a ts = toNthLevel (getNthLevel q) (getInterTemporalMatching q) (getNthCluster q) phylo1
where where
-------------------------------------- --------------------------------------
phylo1 :: Phylo phylo1 :: Phylo
...@@ -213,8 +216,8 @@ toPhylo q c a = toNthLevel (getNthLevel q) (getInterTemporalMatching q) (getNthC ...@@ -213,8 +216,8 @@ toPhylo q c a = toNthLevel (getNthLevel q) (getInterTemporalMatching q) (getNthC
phylo0 = toPhylo0 phyloDocs phyloBase phylo0 = toPhylo0 phyloDocs phyloBase
-------------------------------------- --------------------------------------
phyloDocs :: Map (Date, Date) [Document] phyloDocs :: Map (Date, Date) [Document]
phyloDocs = corpusToDocs groupNgramsWithTrees c phyloBase phyloDocs = corpusToDocs c phyloBase
-------------------------------------- --------------------------------------
phyloBase :: Phylo phyloBase :: Phylo
phyloBase = toPhyloBase q (initPhyloParam (Just defaultPhyloVersion) (Just defaultSoftware) (Just q)) c a phyloBase = toPhyloBase q (initPhyloParam (Just defaultPhyloVersion) (Just defaultSoftware) (Just q)) c a ts
-------------------------------------- --------------------------------------
\ No newline at end of file
...@@ -133,28 +133,30 @@ unifySharedKeys m1 m2 = mapKeys (\(x,y) -> if member (y,x) m2 ...@@ -133,28 +133,30 @@ unifySharedKeys m1 m2 = mapKeys (\(x,y) -> if member (y,x) m2
--------------- ---------------
-- | An analyzer ingests a Ngrams and generates a modified version of it
phyloAnalyzer :: Ngrams -> Ngrams
phyloAnalyzer n = toLower n
-- | To init the foundation of the Phylo as a Vector of Ngrams -- | To init the foundation of the Phylo as a Vector of Ngrams
initFoundations :: [Ngrams] -> Vector Ngrams initFoundations :: [Ngrams] -> Vector Ngrams
initFoundations l = Vector.fromList $ map toLower l initFoundations l = Vector.fromList $ map phyloAnalyzer l
-- | To init the base of a Phylo from a List of Periods and Foundations -- | To init the base of a Phylo from a List of Periods and Foundations
initPhyloBase :: [(Date, Date)] -> Vector Ngrams -> PhyloParam -> Phylo initPhyloBase :: [(Date, Date)] -> Vector Ngrams -> PhyloPeaks -> PhyloParam -> Phylo
initPhyloBase pds fds prm = Phylo ((fst . head) pds, (snd . last) pds) fds (map (\pd -> initPhyloPeriod pd []) pds) prm initPhyloBase pds fds pks prm = Phylo ((fst . head) pds, (snd . last) pds) fds pks (map (\pd -> initPhyloPeriod pd []) pds) prm
-- | To init the param of a Phylo -- | To init the param of a Phylo
initPhyloParam :: Maybe Text -> Maybe Software -> Maybe PhyloQuery -> PhyloParam initPhyloParam :: Maybe Text -> Maybe Software -> Maybe PhyloQuery -> PhyloParam
initPhyloParam (def defaultPhyloVersion -> v) (def defaultSoftware -> s) (def defaultQuery -> q) = PhyloParam v s q initPhyloParam (def defaultPhyloVersion -> v) (def defaultSoftware -> s) (def defaultQuery -> q) = PhyloParam v s q
-- | To get the foundations of a Phylo -- | To get the foundations of a Phylo
getFoundations :: Phylo -> Vector Ngrams getFoundations :: Phylo -> Vector Ngrams
getFoundations = _phylo_foundations getFoundations = _phylo_foundations
-- | To get the Index of a Ngrams in the Foundations of a Phylo -- | To get the Index of a Ngrams in the Foundations of a Phylo
getIdxInFoundations :: Ngrams -> Phylo -> Int getIdxInFoundations :: Ngrams -> Phylo -> Int
getIdxInFoundations n p = case (elemIndex n (getFoundations p)) of getIdxInFoundations n p = case (elemIndex n (getFoundations p)) of
Nothing -> panic "[ERR][Viz.Phylo.Tools.getFoundationIdx] Ngrams not in Foundations" Nothing -> panic "[ERR][Viz.Phylo.Tools.getIdxInFoundations] Ngrams not in Foundations"
Just idx -> idx Just idx -> idx
...@@ -167,6 +169,54 @@ getLastLevel p = (last . sort) ...@@ -167,6 +169,54 @@ getLastLevel p = (last . sort)
. phylo_periodLevels ) p . phylo_periodLevels ) p
--------------------
-- | PhyloPeaks | --
--------------------
-- | To apply a fonction to each label of a Ngrams Tree
alterLabels :: (Ngrams -> Ngrams) -> Tree Ngrams -> Tree Ngrams
alterLabels f (Node lbl ns) = Node (f lbl) (map (\n -> alterLabels f n) ns)
-- | To transform a forest of trees into a map (node,root)
forestToMap :: [Tree Ngrams] -> Map Ngrams Ngrams
forestToMap trees = Map.fromList $ concat $ map (\(Node lbl ns) -> treeToTuples (Node lbl ns) lbl) trees
-- | To get the foundationsPeaks of a Phylo
getPeaks :: Phylo -> PhyloPeaks
getPeaks = _phylo_foundationsPeaks
-- | To get the peaksLabels of a Phylo
getPeaksLabels :: Phylo -> Vector Ngrams
getPeaksLabels p = (getPeaks p) ^. phylo_peaksLabels
-- | To get the Index of a Ngrams in the foundationsPeaks of a Phylo
getIdxInPeaks :: Ngrams -> Phylo -> Int
getIdxInPeaks n p = case (elemIndex n (getPeaksLabels p)) of
Nothing -> panic "[ERR][Viz.Phylo.Tools.getIdxInPeaks] Ngrams not in foundationsPeaks"
Just idx -> idx
-- | To init the PhyloPeaks of a Phylo
initPeaks :: [Tree Ngrams] -> Vector Ngrams -> PhyloPeaks
initPeaks trees ns = PhyloPeaks labels trees
where
--------------------------------------
labels :: Vector Ngrams
labels = Vector.fromList
$ nub
$ Vector.toList
$ map (\n -> if member n mTrees
then mTrees Map.! n
else n ) ns
--------------------------------------
mTrees :: Map Ngrams Ngrams
mTrees = forestToMap trees
--------------------------------------
-- | To transform a Ngrams Tree into a list of (node,root)
treeToTuples :: Tree Ngrams -> Ngrams -> [(Ngrams,Ngrams)]
treeToTuples (Node lbl ns) root = [(lbl,root)] ++ (concat $ map (\n -> treeToTuples n root) ns)
-------------------- --------------------
-- | PhyloGroup | -- -- | PhyloGroup | --
-------------------- --------------------
...@@ -327,7 +377,7 @@ initGroup :: [Ngrams] -> Text -> Int -> Int -> Int -> Int -> Phylo -> PhyloGroup ...@@ -327,7 +377,7 @@ initGroup :: [Ngrams] -> Text -> Int -> Int -> Int -> Int -> Phylo -> PhyloGroup
initGroup ngrams lbl idx lvl from to p = PhyloGroup initGroup ngrams lbl idx lvl from to p = PhyloGroup
(((from, to), lvl), idx) (((from, to), lvl), idx)
lbl lbl
(sort $ map (\x -> getIdxInFoundations x p) ngrams) (sort $ map (\x -> getIdxInPeaks x p) ngrams)
(Map.empty) (Map.empty)
(Map.empty) (Map.empty)
Nothing Nothing
......
...@@ -83,7 +83,7 @@ alterBranchLabel (id,lbl) v = over (phylo_viewBranches ...@@ -83,7 +83,7 @@ alterBranchLabel (id,lbl) v = over (phylo_viewBranches
-- | To set the label of a PhyloBranch as the nth most frequent terms of its PhyloNodes -- | To set the label of a PhyloBranch as the nth most frequent terms of its PhyloNodes
branchLabelFreq :: PhyloView -> Int -> Phylo -> PhyloView branchLabelFreq :: PhyloView -> Int -> Phylo -> PhyloView
branchLabelFreq v thr p = foldl (\v' (id,lbl) -> alterBranchLabel (id,lbl) v') v branchLabelFreq v thr p = foldl (\v' (id,lbl) -> alterBranchLabel (id,lbl) v') v
$ map (\(id,ns) -> (id, freqToLabel thr (getFoundations p) $ map (\(id,ns) -> (id, freqToLabel thr (getPeaksLabels p)
$ getGroupsFromNodes ns p)) $ getGroupsFromNodes ns p))
$ getNodesByBranches v $ getNodesByBranches v
...@@ -92,7 +92,7 @@ branchLabelFreq v thr p = foldl (\v' (id,lbl) -> alterBranchLabel (id,lbl) v') v ...@@ -92,7 +92,7 @@ branchLabelFreq v thr p = foldl (\v' (id,lbl) -> alterBranchLabel (id,lbl) v') v
nodeLabelCooc :: PhyloView -> Int -> Phylo -> PhyloView nodeLabelCooc :: PhyloView -> Int -> Phylo -> PhyloView
nodeLabelCooc v thr p = over (phylo_viewNodes nodeLabelCooc v thr p = over (phylo_viewNodes
. traverse) . traverse)
(\n -> let lbl = ngramsToLabel (getFoundations p) (\n -> let lbl = ngramsToLabel (getPeaksLabels p)
$ mostOccNgrams thr $ mostOccNgrams thr
$ head $ getGroupsFromIds [getNodeId n] p $ head $ getGroupsFromIds [getNodeId n] p
in n & phylo_nodeLabel .~ lbl) v in n & phylo_nodeLabel .~ lbl) v
......
...@@ -56,7 +56,7 @@ initPhyloEdge id pts et = map (\pt -> PhyloEdge id (fst pt) et (snd pt)) pts ...@@ -56,7 +56,7 @@ initPhyloEdge id pts et = map (\pt -> PhyloEdge id (fst pt) et (snd pt)) pts
initPhyloView :: Level -> Text -> Text -> Filiation -> Bool -> Phylo -> PhyloView initPhyloView :: Level -> Text -> Text -> Filiation -> Bool -> Phylo -> PhyloView
initPhyloView lvl lbl dsc fl vb p = PhyloView (getPhyloParams p) lbl dsc fl empty initPhyloView lvl lbl dsc fl vb p = PhyloView (getPhyloParams p) lbl dsc fl empty
([] ++ (phyloToBranches lvl p)) ([] ++ (phyloToBranches lvl p))
([] ++ (groupsToNodes True vb (getFoundations p) gs)) ([] ++ (groupsToNodes True vb (getPeaksLabels p) gs))
([] ++ (groupsToEdges fl PeriodEdge gs)) ([] ++ (groupsToEdges fl PeriodEdge gs))
where where
-------------------------------------- --------------------------------------
...@@ -126,7 +126,7 @@ addChildNodes shouldDo lvl lvlMin vb fl p v = ...@@ -126,7 +126,7 @@ addChildNodes shouldDo lvl lvlMin vb fl p v =
then v then v
else addChildNodes shouldDo (lvl - 1) lvlMin vb fl p else addChildNodes shouldDo (lvl - 1) lvlMin vb fl p
$ v & phylo_viewBranches %~ (++ (phyloToBranches (lvl - 1) p)) $ v & phylo_viewBranches %~ (++ (phyloToBranches (lvl - 1) p))
& phylo_viewNodes %~ (++ (groupsToNodes False vb (getFoundations p) gs')) & phylo_viewNodes %~ (++ (groupsToNodes False vb (getPeaksLabels p) gs'))
& phylo_viewEdges %~ (++ (groupsToEdges fl PeriodEdge gs')) & phylo_viewEdges %~ (++ (groupsToEdges fl PeriodEdge gs'))
& phylo_viewEdges %~ (++ (groupsToEdges Descendant LevelEdge gs )) & phylo_viewEdges %~ (++ (groupsToEdges Descendant LevelEdge gs ))
& phylo_viewEdges %~ (++ (groupsToEdges Ascendant LevelEdge gs')) & phylo_viewEdges %~ (++ (groupsToEdges Ascendant LevelEdge gs'))
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment