Commit 25947869 authored by Quentin Lobbé's avatar Quentin Lobbé

End of refactoring, put some function inside Tools.hs

parent a0ceace8
Pipeline #244 failed with stage
......@@ -168,6 +168,16 @@ data LevelLink =
, _levelTo :: Level
} deriving (Show)
-- | Document : a piece of Text linked to a Date
data Document = Document
{ date :: Date
, text :: Text
} deriving (Show)
data PhyloError = LevelDoesNotExist
| LevelUnassigned
deriving (Show)
-- | Lenses
makeLenses ''Phylo
makeLenses ''PhyloParam
......
......@@ -28,90 +28,50 @@ TODO:
module Gargantext.Viz.Phylo.Example where
import Control.Lens hiding (makeLenses, both, Level)
import Data.Bool (Bool, not)
import Data.List (concat, union, intersect, tails, tail, head, last, null, zip, sort, length, any, (++), nub)
import qualified Data.List as List
import Data.Map (Map, elems, member, adjust, singleton, (!), keys, restrictKeys, mapWithKey)
import Data.Semigroup (Semigroup)
import Data.Set (Set)
import Data.Text (Text, unwords, toLower, words)
import Data.Tuple (fst, snd)
import Data.Tuple.Extra
import Data.Semigroup (Semigroup)
import Data.Map (Map, elems, member, adjust, singleton, (!), keys, restrictKeys, mapWithKey)
import qualified Data.Map as Map
import Data.Vector (Vector, fromList, elemIndex)
import qualified Data.Vector as Vector
import qualified Data.Maybe as Maybe
import Data.Tuple (fst, snd)
import qualified Data.Tuple as Tuple
import Data.Bool (Bool, not)
import qualified Data.Bool as Bool
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Data.Matrix as DM'
import Gargantext.Prelude hiding (head)
import Gargantext.Text.Metrics.FrequentItemSet (fisWithSizePolyMap, Size(..))
import Gargantext.Text.Terms.Mono (monoTexts)
import Gargantext.Prelude hiding (head)
import Gargantext.Viz.Phylo
import Gargantext.Viz.Phylo.Tools
------------------------------------------------------------------------
-- | Types | --
-- | Document : a piece of Text linked to a Date
data Document = Document
{ date :: Date
, text :: Text
} deriving (Show)
-- | Corpus : a list of Documents
type Corpus = [Document]
type PeriodeSize = Int
-- data Periodes b a = Map (b,b) a
type Occurrences = Int
data LinkLvlLabel = Link_m1_0 | Link_0_m1 | Link_1_0 | Link_0_1 | Link_x_y
deriving (Show, Eq, Enum, Bounded)
data LinkLvl = LinkLvl
{ linkLvlLabel :: LinkLvlLabel
, linkLvlFrom :: Int
, linkLvlTo :: Int
} deriving (Show)
data PhyloError = LevelDoesNotExist
| LevelUnassigned
deriving (Show)
import qualified Data.Bool as Bool
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Maybe as Maybe
import qualified Data.Set as Set
import qualified Data.Tuple as Tuple
import qualified Data.Vector as Vector
--------------------------------------------------------------------
phyloExampleFinal :: Phylo
phyloExampleFinal = undefined
------------------------------------------------------------------------
-- | STEP 12 | -- Incrementaly cluster the PhyloGroups n times, link them through the Periods and build level n of the Phylo
--------------------------------------------------------------------
appariement :: Map (Date, Date) (Map (Set Ngrams) Int)
appariement = undefined
------------------------------------------------------------------------
-- | STEP 10 | -- Incrementaly cluster the PhyloGroups n times, link them through the Periods and build level n of the Phylo
-- | STEP 11 | -- Cluster the Fis
------------------------------------------------------------------------
-- | STEP 8 | -- Cluster the Fis
-- | STEP 10 | -- Link the PhyloGroups of level 1 through the Periods
------------------------------------------------------------------------
-- | STEP 9 | -- Link the PhyloGroups of level 1 through the Periods
-- | To pair two PhyloGroups sharing at leats one Ngrams
shouldPair :: PhyloGroup -> PhyloGroup -> Bool
shouldPair g g' = (not . null) $ intersect (getGroupNgrams g) (getGroupNgrams g')
-- | To get the good pair of keys (x,y) or (y,x) in a given Map (a,b) c
getKeyPair :: (Int,Int) -> Map (Int,Int) a -> (Int,Int)
getKeyPair (x,y) m = case findPair (x,y) m of
Nothing -> panic "[ERR][Viz.Phylo.Example.getKeyPair] Nothing"
......@@ -125,12 +85,14 @@ getKeyPair (x,y) m = case findPair (x,y) m of
| otherwise = Nothing
--------------------------------------
-- |
-- | To get all combinations of a list with no repetition and apply a function to the resulting list of pairs
listToCombi :: forall a b. (a -> b) -> [a] -> [(b,b)]
listToCombi f l = [ (f x, f y) | (x:rest) <- tails l
, y <- rest
]
, y <- rest ]
-- | To transform the Fis into a coocurency Matrix in a Phylo
fisToCooc :: Map (Date, Date) Fis -> Phylo -> Map (Int, Int) Double
fisToCooc m p = map (/docs)
$ foldl (\mem x -> adjust (+1) (getKeyPair x mem) mem) cooc
......@@ -152,28 +114,15 @@ fisToCooc m p = map (/docs)
--------------------------------------
phyloWithAppariement1 :: Phylo
phyloWithAppariement1 = phyloLinked_0_1
------------------------------------------------------------------------
-- | STEP 8 | -- Find the Fis out of Documents and Ngrams and build level 1 of the Phylo
phyloLinked_0_1 :: Phylo
phyloLinked_0_1 = phyloToLinks lvl_0_1 phyloLinked_1_0
lvl_0_1 :: LinkLvl
lvl_0_1 = (LinkLvl Link_0_1 0 1)
phyloLinked_1_0 :: Phylo
phyloLinked_1_0 = phyloToLinks lvl_1_0 phyloWithGroups1
------------------------------------------------------------------------
-- | STEP 9 | -- Build level 1 of the Phylo
lvl_1_0 :: LinkLvl
lvl_1_0 = (LinkLvl Link_1_0 1 0)
phyloWithGroups1 :: Phylo
phyloWithGroups1 = updatePhyloByLevel (initLevel 1 Level_1) phyloLinked_m1_0
-- | To Cliques into Groups
cliqueToGroup :: PhyloPeriodId -> Int -> Int -> Ngrams -> (Clique,Support) -> Phylo -> PhyloGroup
cliqueToGroup period lvl idx label fis p = PhyloGroup ((period, lvl), idx)
label
......@@ -184,6 +133,8 @@ cliqueToGroup period lvl idx label fis p = PhyloGroup ((period, lvl), idx)
(singleton "support" (fromIntegral $ snd fis))
[] [] [] []
-- | To transform Fis into PhyloLevels
fisToPhyloLevel :: Map (Date, Date) Fis -> Phylo -> Phylo
fisToPhyloLevel m p = over (phylo_periods . traverse)
(\period ->
......@@ -192,67 +143,80 @@ fisToPhyloLevel m p = over (phylo_periods . traverse)
in over (phylo_periodLevels)
(\levels ->
let groups = map (\fis -> cliqueToGroup periodId 1 (fst fis) "" (snd fis) p) fisList
in (PhyloLevel (periodId, 1) groups) : levels
) period
) p
in levels ++ [PhyloLevel (periodId, 1) groups]
) period ) p
phyloLinked_0_1 :: Phylo
phyloLinked_0_1 = alterLevelLinks lvl_0_1 phyloLinked_1_0
lvl_0_1 :: LevelLink
lvl_0_1 = initLevelLink (initLevel 0 Level_0) (initLevel 1 Level_1)
phyloLinked_1_0 :: Phylo
phyloLinked_1_0 = alterLevelLinks lvl_1_0 phyloWithGroups1
lvl_1_0 :: LevelLink
lvl_1_0 = initLevelLink (initLevel 1 Level_1) (initLevel 0 Level_0)
phyloWithGroups1 :: Phylo
phyloWithGroups1 = updatePhyloByLevel (initLevel 1 Level_1) phyloLinked_m1_0
-- | To preserve nonempty periods from filtering, please use : filterFisBySupport False ...
phyloFisFiltered :: Map (Date, Date) Fis
phyloFisFiltered = filterFisBySupport True 1 (filterFisByNested phyloFis)
------------------------------------------------------------------------
-- | STEP 8 | -- Create Frequent Items Sets by Period and filter them
-- | To Filter Fis by support
filterFisBySupport :: Bool -> Int -> Map (Date, Date) Fis -> Map (Date, Date) Fis
filterFisBySupport empty min m = case empty of
True -> Map.map (\fis -> filterMinorFis min fis) m
False -> Map.map (\fis -> filterMinorFisNonEmpty min fis) m
-- | To filter Fis with small Support, to preserve nonempty periods please use : filterFisBySupport False
filterMinorFis :: Int -> Fis -> Fis
filterMinorFis min fis = Map.filter (\s -> s > min) fis
-- | To filter Fis with small Support but by keeping non empty Periods
filterMinorFisNonEmpty :: Int -> Fis -> Fis
filterMinorFisNonEmpty min fis = if (Map.null fis') && (not $ Map.null fis)
then filterMinorFisNonEmpty (min - 1) fis
else fis'
where
--------------------------------------
fis' :: Fis
fis' = filterMinorFis min fis
doesContains :: [Ngrams] -> [Ngrams] -> Bool
doesContains l l'
| null l' = True
| length l' > length l = False
| elem (head l') l = doesContains l (tail l')
| otherwise = False
doesAnyContains :: Set Ngrams -> [Set Ngrams] -> [Set Ngrams] -> Bool
doesAnyContains h l l' = any (\c -> doesContains (Set.toList c) (Set.toList h)) (l' ++ l)
filterNestedCliques :: Set Ngrams -> [Set Ngrams] -> [Set Ngrams] -> [Set Ngrams]
filterNestedCliques h l l'
| null l = if doesAnyContains h l l'
then l'
else h : l'
| doesAnyContains h l l' = filterNestedCliques (head l) (tail l) l'
| otherwise = filterNestedCliques (head l) (tail l) (h : l')
--------------------------------------
-- | To filter nested Fis
filterFisByNested :: Map (Date, Date) Fis -> Map (Date, Date) Fis
filterFisByNested = map (\fis -> restrictKeys fis
$ Set.fromList
$ filterNestedCliques (head (keys fis)) (keys fis) []
$ filterNestedSets (head (keys fis)) (keys fis) []
)
phyloFis :: Map (Date, Date) Fis
phyloFis = termsToFis phyloPeriods
termsToFis :: Map (Date, Date) [Document]
-> Map (Date, Date) Fis
termsToFis = corpusToFis (words . text)
-- | To transform a list of Documents into a Frequent Items Set
docsToFis :: Map (Date, Date) [Document] -> Map (Date, Date) Fis
docsToFis docs = map (\d -> fisWithSizePolyMap
(Segment 1 20)
1
(map (words . text) d)) docs
phyloFisFiltered :: Map (Date, Date) Fis
phyloFisFiltered = filterFisBySupport True 1 (filterFisByNested phyloFis)
-- | TODO: parameters has to be checked
-- | TODO FIS on monotexts
corpusToFis :: (Document -> [Ngrams])
-> Map (Date, Date) [Document]
-> Map (Date, Date) (Map (Set Ngrams) Int)
corpusToFis f = map (\d -> fisWithSizePolyMap (Segment 1 20) 1 (map f d))
phyloFis :: Map (Date, Date) Fis
phyloFis = docsToFis phyloPeriods
------------------------------------------------------------------------
......@@ -260,80 +224,59 @@ corpusToFis f = map (\d -> fisWithSizePolyMap (Segment 1 20) 1 (map f d))
phyloLinked_m1_0 :: Phylo
phyloLinked_m1_0 = phyloToLinks lvl_m1_0 phyloLinked_0_m1
phyloLinked_m1_0 = alterLevelLinks lvl_m1_0 phyloLinked_0_m1
lvl_m1_0 :: LinkLvl
lvl_m1_0 = (LinkLvl Link_m1_0 (-1) 0)
lvl_m1_0 :: LevelLink
lvl_m1_0 = initLevelLink (initLevel (-1) Level_m1) (initLevel 0 Level_0)
------------------------------------------------------------------------
-- | STEP 6 | -- Link level 0 to level -1
addPointer :: Semigroup field
=> ASetter current target identity (field -> field)
-> field -> current -> target
addPointer field targetPointer current =
set field (<> targetPointer) current
containsIdx :: [Int] -> [Int] -> Bool
containsIdx l l'
| null l' = False
| last l < head l' = False
| head l' `elem` l = True
| otherwise = containsIdx l (tail l')
shouldLink :: LinkLvl -> [Int] -> [Int] -> Bool
shouldLink lvl current target = case linkLvlLabel lvl of
Link_0_m1 -> containsIdx target current
Link_m1_0 -> containsIdx target current
Link_0_1 -> containsIdx target current
Link_1_0 -> containsIdx target current
Link_x_y -> undefined
_ -> panic ("error link level to be defined")
linkGroupToGroups :: LinkLvl -> PhyloGroup -> [PhyloGroup] -> PhyloGroup
-- | To set the LevelLinks between a given PhyloGroup and a list of childs/parents PhyloGroups
linkGroupToGroups :: LevelLink -> PhyloGroup -> [PhyloGroup] -> PhyloGroup
linkGroupToGroups lvl current targets
| linkLvlFrom lvl < linkLvlTo lvl = setLevelParents current
| linkLvlFrom lvl > linkLvlTo lvl = setLevelChilds current
| getLevelLinkValue From lvl < getLevelLinkValue To lvl = setLevelParents current
| getLevelLinkValue From lvl > getLevelLinkValue To lvl = setLevelChilds current
| otherwise = current
where
--------------------------------------
setLevelChilds :: PhyloGroup -> PhyloGroup
setLevelChilds = over (phylo_groupLevelChilds) addPointers
--------------------------------------
setLevelParents :: PhyloGroup -> PhyloGroup
setLevelParents = over (phylo_groupLevelParents) addPointers
--------------------------------------
addPointers :: [Pointer] -> [Pointer]
addPointers lp = lp ++ Maybe.mapMaybe (\target -> if shouldLink lvl (_phylo_groupNgrams current)
addPointers lp = lp ++ Maybe.mapMaybe (\target ->
if shouldLink lvl (_phylo_groupNgrams current)
(_phylo_groupNgrams target )
then Just ((getGroupId target),1)
else Nothing
) targets
else Nothing) targets
--------------------------------------
addPointers' :: [Pointer] -> [Pointer]
addPointers' lp = lp ++ map (\target -> ((getGroupId target),1)) targets
linkGroupsByLevel :: LinkLvl -> Phylo -> [PhyloGroup] -> [PhyloGroup]
-- | To set the LevelLinks between two lists of PhyloGroups
linkGroupsByLevel :: LevelLink -> Phylo -> [PhyloGroup] -> [PhyloGroup]
linkGroupsByLevel lvl p groups = map (\group ->
if getGroupLevel group == linkLvlFrom lvl
then linkGroupToGroups lvl group (getGroupsWithFilters (linkLvlTo lvl) (getGroupPeriod group) p)
if getGroupLevel group == getLevelLinkValue From lvl
then linkGroupToGroups lvl group (getGroupsWithFilters (getLevelLinkValue To lvl) (getGroupPeriod group) p)
else group ) groups
phyloToLinks :: LinkLvl -> Phylo -> Phylo
phyloToLinks lvl p = over ( phylo_periods
. traverse
. phylo_periodLevels
. traverse
. phylo_levelGroups
)
(linkGroupsByLevel lvl p) p
-- | To set the LevelLink of all the PhyloGroups of a Phylo
alterLevelLinks :: LevelLink -> Phylo -> Phylo
alterLevelLinks lvl p = alterPhyloGroups (linkGroupsByLevel lvl p) p
phyloLinked_0_m1 :: Phylo
phyloLinked_0_m1 = phyloToLinks lvl_0_m1 phyloWithGroups0
phyloLinked_0_m1 = alterLevelLinks lvl_0_m1 phyloWithGroups0
lvl_0_m1 :: LinkLvl
lvl_0_m1 = (LinkLvl Link_0_m1 0 (-1))
lvl_0_m1 :: LevelLink
lvl_0_m1 = initLevelLink (initLevel 0 Level_0) (initLevel (-1) Level_m1)
------------------------------------------------------------------------
......@@ -346,6 +289,7 @@ clonePhyloLevel lvl p = alterPhyloLevels (\l -> addPhyloLevel
(setPhyloLevelId lvl $ head l)
l) p
phyloWithGroups0 :: Phylo
phyloWithGroups0 = updatePhyloByLevel (initLevel 0 Level_0) phyloWithGroupsm1
......@@ -363,7 +307,8 @@ docsToPhyloLevel lvl (d, d') docs p = initPhyloLevel
$ (nub . concat)
$ map (words . text) docs)
-- | To transform a Map of Periods and Documents into a list of [PhyloPeriod]
-- | To transform a Map of Periods and Documents into a list of PhyloPeriods
docsToPhyloPeriods :: Int -> Map (Date,Date) [Document] -> Phylo -> [PhyloPeriod]
docsToPhyloPeriods lvl docs p = map (\(id,l) -> initPhyloPeriod id l)
$ Map.toList levels
......@@ -373,6 +318,7 @@ docsToPhyloPeriods lvl docs p = map (\(id,l) -> initPhyloPeriod id l)
levels = mapWithKey (\k v -> [docsToPhyloLevel lvl k v p]) docs
--------------------------------------
-- | To update a Phylo for a given Levels
updatePhyloByLevel :: Level -> Phylo -> Phylo
updatePhyloByLevel lvl p
......@@ -387,10 +333,16 @@ updatePhyloByLevel lvl p
Level_0 -> clonePhyloLevel (getLevelValue lvl) p
Level_1 -> fisToPhyloLevel phyloFisFiltered p
Level_1 -> fisToPhyloLevel lvlData p
where
--------------------------------------
lvlData :: Map (Date, Date) Fis
lvlData = phyloFisFiltered
--------------------------------------
_ -> panic ("[ERR][Viz.Phylo.Example.updatePhyloByLevel] Level not defined")
phyloWithGroupsm1 :: Phylo
phyloWithGroupsm1 = updatePhyloByLevel (initLevel (-1) Level_m1) phylo
......@@ -417,17 +369,20 @@ docsToPeriods f g s es = Map.fromList $ zip hs $ map (inPeriode f es) hs
$ chunkAlong s' o' [start .. end]
--------------------------------------
-- | To parse a list of Documents by filtering on a Vector of Ngrams
parseDocs :: PhyloNgrams -> [Document] -> [Document]
parseDocs l docs = map (\(Document d t) -> Document d (unwords
$ filter (\x -> Vector.elem x l)
$ monoTexts t)) docs
-- | To group a list of Documents by fixed periods
groupDocsByPeriod :: Grain -> Step -> [Document] -> Phylo -> Map (Date, Date) [Document]
groupDocsByPeriod g s docs p = docsToPeriods date g s
$ parseDocs (getPhyloNgrams p) docs
phyloPeriods :: Map (Date, Date) [Document]
phyloPeriods = groupDocsByPeriod 5 3 phyloDocs phylo
......@@ -440,10 +395,12 @@ phyloPeriods = groupDocsByPeriod 5 3 phyloDocs phylo
initPhylo :: [Document] -> PhyloNgrams -> Phylo
initPhylo docs ngrams = Phylo (both date $ (last &&& head) docs) ngrams []
-- | To init a PhyloNgrams as a Vector of Ngrams
initNgrams :: [Ngrams] -> PhyloNgrams
initNgrams l = Vector.fromList $ map toLower l
phylo :: Phylo
phylo = initPhylo phyloDocs (initNgrams actants)
......@@ -456,6 +413,7 @@ phylo = initPhylo phyloDocs (initNgrams actants)
corpusToDocs :: [(Date, Text)] -> [Document]
corpusToDocs l = map (\(d,t) -> Document d t) l
phyloDocs :: [Document]
phyloDocs = corpusToDocs corpus
......@@ -469,6 +427,6 @@ actants = [ "Cleopatre" , "Ptolemee", "Ptolemee-XIII", "Ptolemee-XIV"
, "Marc-Antoine", "Cesar" , "Antoine" , "Octave" , "Rome"
, "Alexandrie" , "Auguste" , "Pompee" , "Cassius" , "Brutus"]
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")]
\ No newline at end of file
......@@ -18,18 +18,131 @@ module Gargantext.Viz.Phylo.Tools
where
import Control.Lens hiding (both, Level)
import Data.List (filter, intersect, (++), sort)
import Data.List (filter, intersect, (++), sort, null, head, tail, last)
import Data.Map (Map)
import Data.Set (Set)
import Data.Text (Text)
import Data.Tuple.Extra
import Data.Vector (Vector,elemIndex)
import Gargantext.Prelude hiding (head)
import Gargantext.Viz.Phylo
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Set as Set
------------------------------------------------------------------------
-- | Generic Tools | --
-- | Tools | --
-- | To add a PhyloLevel at the end of a list of PhyloLevels
addPhyloLevel :: PhyloLevel -> [PhyloLevel] -> [PhyloLevel]
addPhyloLevel lvl l = l ++ [lvl]
-- | To alter each list of PhyloGroups following a given function
alterPhyloGroups :: ([PhyloGroup] -> [PhyloGroup]) -> Phylo -> Phylo
alterPhyloGroups f p = over ( phylo_periods
. traverse
. phylo_periodLevels
. traverse
. phylo_levelGroups
) f p
-- | To alter each PhyloPeriod of a Phylo following a given function
alterPhyloPeriods :: (PhyloPeriod -> PhyloPeriod) -> Phylo -> Phylo
alterPhyloPeriods f p = over ( phylo_periods
. traverse) f p
-- | To alter a list of PhyloLevels following a given function
alterPhyloLevels :: ([PhyloLevel] -> [PhyloLevel]) -> Phylo -> Phylo
alterPhyloLevels f p = over ( phylo_periods
. traverse
. phylo_periodLevels) f p
-- | To append a list of PhyloPeriod to a Phylo
appendPhyloPeriods :: [PhyloPeriod] -> Phylo -> Phylo
appendPhyloPeriods l p = over (phylo_periods) (++ l) p
-- | Does a List of Sets contains at least one Set of an other List
doesAnySetContains :: Eq a => Set a -> [Set a] -> [Set a] -> Bool
doesAnySetContains h l l' = any (\c -> doesContains (Set.toList c) (Set.toList h)) (l' ++ l)
-- | Does a list of A contains an other list of A
doesContains :: Eq a => [a] -> [a] -> Bool
doesContains l l'
| null l' = True
| length l' > length l = False
| elem (head l') l = doesContains l (tail l')
| otherwise = False
-- | Does a list of ordered A contains an other list of ordered A
doesContainsOrd :: Eq a => Ord a => [a] -> [a] -> Bool
doesContainsOrd l l'
| null l' = False
| last l < head l' = False
| head l' `elem` l = True
| otherwise = doesContainsOrd l (tail l')
-- | To filter the PhyloGroup of a Phylo according to a function and a value
filterGroups :: Eq a => (PhyloGroup -> a) -> a -> Phylo -> [PhyloGroup]
filterGroups f x p = filter (\g -> (f g) == x) (getGroups p)
-- | To filter nested Sets of a
filterNestedSets :: Eq a => Set a -> [Set a] -> [Set a] -> [Set a]
filterNestedSets h l l'
| null l = if doesAnySetContains h l l'
then l'
else h : l'
| doesAnySetContains h l l' = filterNestedSets (head l) (tail l) l'
| otherwise = filterNestedSets (head l) (tail l) (h : l')
-- | To get the id of a PhyloGroup
getGroupId :: PhyloGroup -> PhyloGroupId
getGroupId = _phylo_groupId
-- | To get the level out of the id of a PhyloGroup
getGroupLevel :: PhyloGroup -> Int
getGroupLevel = snd . fst . getGroupId
-- | To get the Ngrams of a PhyloGroup
getGroupNgrams :: PhyloGroup -> [Int]
getGroupNgrams = _phylo_groupNgrams
-- | To get the period out of the id of a PhyloGroup
getGroupPeriod :: PhyloGroup -> (Date,Date)
getGroupPeriod = fst . fst . getGroupId
-- | To get all the PhyloGroup of a Phylo
getGroups :: Phylo -> [PhyloGroup]
getGroups = view ( phylo_periods
. traverse
. phylo_periodLevels
. traverse
. phylo_levelGroups
)
-- | To get all the PhyloGroup of a Phylo with a given level and period
getGroupsWithFilters :: Int -> (Date,Date) -> Phylo -> [PhyloGroup]
getGroupsWithFilters lvl prd p = (filterGroups getGroupLevel lvl p)
`intersect`
(filterGroups getGroupPeriod prd p)
-- | To get the index of an element of a Vector
getIdx :: Eq a => a -> Vector a -> Int
......@@ -37,34 +150,17 @@ getIdx x v = case (elemIndex x v) of
Nothing -> panic "[ERR][Viz.Phylo.Tools.getIndex] Nothing"
Just i -> i
------------------------------------------------------------------------
-- | Phylomemic Tools | --
-- | To create a PhyloGroup in a Phylo out of a list of Ngrams and a set of parameters
initGroup :: [Ngrams] -> Text -> Int -> Int -> Int -> Int -> Phylo -> PhyloGroup
initGroup ngrams lbl idx lvl from to p = PhyloGroup
(((from, to), lvl), idx)
lbl
(sort $ map (\x -> ngramsToIdx x p) ngrams)
(Map.empty)
[] [] [] []
-- | To create a Level
initLevel :: Int -> LevelLabel -> Level
initLevel lvl lbl = Level lbl lvl
-- | To create a LevelLink
initLevelLink :: Level -> Level -> LevelLink
initLevelLink lvl lvl' = LevelLink lvl lvl'
-- | To get the label of a Level
getLevelLabel :: Level -> LevelLabel
getLevelLabel lvl = _levelLabel lvl
-- | To get the value of a Level
getLevelValue :: Level -> Int
getLevelValue lvl = _levelValue lvl
-- | To get the label of a LevelLink based on a Direction
getLevelLinkLabel :: Direction -> LevelLink -> LevelLabel
getLevelLinkLabel dir link = case dir of
......@@ -72,6 +168,7 @@ getLevelLinkLabel dir link = case dir of
To -> view (levelTo . levelLabel) link
_ -> panic "[ERR][Viz.Phylo.Tools.getLevelLinkLabel] Wrong direction"
-- | To get the value of a LevelLink based on a Direction
getLevelLinkValue :: Direction -> LevelLink -> Int
getLevelLinkValue dir link = case dir of
......@@ -79,86 +176,68 @@ getLevelLinkValue dir link = case dir of
To -> view (levelTo . levelValue) link
_ -> panic "[ERR][Viz.Phylo.Tools.getLevelLinkValue] Wrong direction"
-- | To transform an Ngrams into its corresponding index in a Phylo
ngramsToIdx :: Ngrams -> Phylo -> Int
ngramsToIdx x p = getIdx x (_phylo_ngrams p)
-- | To get all the Phylolevels of a given PhyloPeriod
getPhyloLevels :: PhyloPeriod -> [PhyloLevel]
getPhyloLevels = view (phylo_periodLevels)
-- | To get the Ngrams of a Phylo
getPhyloNgrams :: Phylo -> PhyloNgrams
getPhyloNgrams = _phylo_ngrams
-- | To get the Ngrams of a PhyloGroup
getGroupNgrams :: PhyloGroup -> [Int]
getGroupNgrams = _phylo_groupNgrams
-- | To get the id of a PhyloGroup
getGroupId :: PhyloGroup -> PhyloGroupId
getGroupId = _phylo_groupId
-- | To create a PhyloGroup in a Phylo out of a list of Ngrams and a set of parameters
initGroup :: [Ngrams] -> Text -> Int -> Int -> Int -> Int -> Phylo -> PhyloGroup
initGroup ngrams lbl idx lvl from to p = PhyloGroup
(((from, to), lvl), idx)
lbl
(sort $ map (\x -> ngramsToIdx x p) ngrams)
(Map.empty)
[] [] [] []
-- | To get all the PhyloGroup of a Phylo
getGroups :: Phylo -> [PhyloGroup]
getGroups = view ( phylo_periods
. traverse
. phylo_periodLevels
. traverse
. phylo_levelGroups
)
-- | To get the level out of the id of a PhyloGroup
getGroupLevel :: PhyloGroup -> Int
getGroupLevel = snd . fst . getGroupId
-- | To create a Level
initLevel :: Int -> LevelLabel -> Level
initLevel lvl lbl = Level lbl lvl
-- | To get the period out of the id of a PhyloGroup
getGroupPeriod :: PhyloGroup -> (Date,Date)
getGroupPeriod = fst . fst . getGroupId
-- | To filter the PhyloGroup of a Phylo according to a function and a value
filterGroups :: Eq a => (PhyloGroup -> a) -> a -> Phylo -> [PhyloGroup]
filterGroups f x p = filter (\g -> (f g) == x) (getGroups p)
-- | To create a LevelLink
initLevelLink :: Level -> Level -> LevelLink
initLevelLink lvl lvl' = LevelLink lvl lvl'
-- | To get all the PhyloGroup of a Phylo with a given level and period
getGroupsWithFilters :: Int -> (Date,Date) -> Phylo -> [PhyloGroup]
getGroupsWithFilters lvl prd p = (filterGroups getGroupLevel lvl p)
`intersect`
(filterGroups getGroupPeriod prd p)
-- | To create a PhyloLevel
initPhyloLevel :: PhyloLevelId -> [PhyloGroup] -> PhyloLevel
initPhyloLevel id groups = PhyloLevel id groups
-- | To set the LevelId of a PhyloLevel and of all its PhyloGroups
setPhyloLevelId :: Int -> PhyloLevel -> PhyloLevel
setPhyloLevelId lvl' (PhyloLevel (id, lvl) groups)
= PhyloLevel (id, lvl') groups'
where
groups' = over (traverse . phylo_groupId) (\((period, lvl), idx) -> ((period, lvl'), idx)) groups
-- | To get all the Phylolevels of a given PhyloPeriod
getPhyloLevels :: PhyloPeriod -> [PhyloLevel]
getPhyloLevels = view (phylo_periodLevels)
-- | To add a PhyloLevel at the end of a list of PhyloLevels
addPhyloLevel :: PhyloLevel -> [PhyloLevel] -> [PhyloLevel]
addPhyloLevel lvl l = l ++ [lvl]
-- | To alter a list of PhyloLevels following a given function
alterPhyloLevels :: ([PhyloLevel] -> [PhyloLevel]) -> Phylo -> Phylo
alterPhyloLevels f p = over ( phylo_periods
. traverse
. phylo_periodLevels) f p
-- | To create a PhyloPeriod
initPhyloPeriod :: PhyloPeriodId -> [PhyloLevel] -> PhyloPeriod
initPhyloPeriod id l = PhyloPeriod id l
-- | To alter each PhyloPeriod of a Phylo following a given function
alterPhyloPeriods :: (PhyloPeriod -> PhyloPeriod) -> Phylo -> Phylo
alterPhyloPeriods f p = over ( phylo_periods
. traverse) f p
-- | To append a list of PhyloPeriod to a Phylo
appendPhyloPeriods :: [PhyloPeriod] -> Phylo -> Phylo
appendPhyloPeriods l p = over (phylo_periods) (++ l) p
-- | To transform an Ngrams into its corresponding index in a Phylo
ngramsToIdx :: Ngrams -> Phylo -> Int
ngramsToIdx x p = getIdx x (_phylo_ngrams p)
-- | To set the LevelId of a PhyloLevel and of all its PhyloGroups
setPhyloLevelId :: Int -> PhyloLevel -> PhyloLevel
setPhyloLevelId lvl' (PhyloLevel (id, lvl) groups)
= PhyloLevel (id, lvl') groups'
where
groups' = over (traverse . phylo_groupId) (\((period, lvl), idx) -> ((period, lvl'), idx)) groups
-- | To choose a LevelLink strategy based an a given Level
shouldLink :: LevelLink -> [Int] -> [Int] -> Bool
shouldLink lvl l l'
| from <= 1 = doesContainsOrd l l'
| from > 1 = undefined
| otherwise = panic ("[ERR][Viz.Phylo.Tools.shouldLink] LevelLink not defined")
where
--------------------------------------
from :: Int
from = getLevelLinkValue From lvl
--------------------------------------
\ No newline at end of file
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