2 Module : Gargantext.Viz.Phylo
3 Description : Phylomemy definitions and types.
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Specifications of Phylomemy export format.
12 Phylomemy can be described as a Temporal Graph with different scale of
13 granularity of group of ngrams (terms and multi-terms).
15 The main type is Phylo which is synonym of Phylomemy (only difference is
19 Chavalarias, D., Cointet, J.-P., 2013. Phylomemetic patterns
20 in science evolution — the rise and fall of scientific fields. PloS
25 {-# LANGUAGE DeriveGeneric #-}
26 {-# LANGUAGE NoImplicitPrelude #-}
27 {-# LANGUAGE TemplateHaskell #-}
29 module Gargantext.Viz.Phylo where
31 import Control.Lens (makeLenses)
32 import Data.Aeson.TH (deriveJSON)
33 import Data.Maybe (Maybe)
34 import Data.Text (Text)
35 import Data.Time.Clock.POSIX (POSIXTime)
36 import GHC.Generics (Generic)
37 import Gargantext.Database.Schema.Ngrams (NgramsId)
38 import Gargantext.Core.Utils.Prefix (unPrefix)
39 import Gargantext.Prelude
41 ------------------------------------------------------------------------
43 PhyloExport { _phyloExport_param :: PhyloParam
44 , _phyloExport_data :: Phylo
47 -- | .phylo parameters
49 PhyloParam { _phyloParam_version :: Text -- Double ?
50 , _phyloParam_software :: Software
51 , _phyloParam_params :: Hash
57 -- TODO move somewhere since it is generic
59 Software { _software_name :: Text
60 , _software_version :: Text
63 ------------------------------------------------------------------------
64 -- | Phylo datatype descriptor of a phylomemy
65 -- Duration : time Segment of the whole phylomemy (start,end)
66 -- Ngrams : list of all (possible) terms contained in the phylomemy (with their id)
67 -- Steps : list of all steps to build the phylomemy
69 Phylo { _phylo_duration :: (Start, End)
70 , _phylo_ngrams :: [Ngram]
71 , _phylo_periods :: [PhyloPeriod]
75 -- | UTCTime in seconds since UNIX epoch
76 type Start = POSIXTime
80 type Ngram = (NgramsId, Text)
82 -- | PhyloStep : steps of phylomemy on temporal axis
83 -- Period: tuple (start date, end date) of the step of the phylomemy
84 -- Levels: levels of granularity
86 PhyloPeriod { _phylo_periodId :: PhyloPeriodId
87 , _phylo_periodLevels :: [PhyloLevel]
91 type PhyloPeriodId = (Start, End)
93 -- | PhyloLevel : levels of phylomemy on level axis
94 -- Levels description:
95 -- Level -1: Ngram equals itself (by identity) == _phylo_Ngrams
96 -- Level 0: Group of synonyms (by stems + by qualitative expert meaning)
97 -- Level 1: First level of clustering
98 -- Level N: Nth level of clustering
100 PhyloLevel { _phylo_levelId :: PhyloLevelId
101 , _phylo_levelGroups :: [PhyloGroup]
105 type PhyloLevelId = (PhyloPeriodId, Int)
107 -- | PhyloGroup : group of ngrams at each level and step
108 -- Label : maybe has a label as text
109 -- Ngrams: set of terms that build the group
110 -- Period Parents|Childs: weighted link to Parents|Childs (Temporal Period axis)
111 -- Level Parents|Childs: weighted link to Parents|Childs (Level Granularity axis)
112 -- Pointers are directed link from Self to any PhyloGroup (/= Self ?)
114 PhyloGroup { _phylo_groupId :: PhyloGroupId
115 , _phylo_groupLabel :: Maybe Text
116 , _phylo_groupNgrams :: [NgramsId]
118 , _phylo_groupPeriodParents :: [Pointer]
119 , _phylo_groupPeriodChilds :: [Pointer]
121 , _phylo_groupLevelParents :: [Pointer]
122 , _phylo_groupLevelChilds :: [Pointer]
126 type PhyloGroupId = (PhyloLevelId, Int)
127 type Pointer = (PhyloGroupId, Weight)
132 makeLenses ''PhyloParam
133 makeLenses ''PhyloExport
134 makeLenses ''Software
137 $(deriveJSON (unPrefix "_phylo_" ) ''Phylo )
138 $(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod )
139 $(deriveJSON (unPrefix "_phylo_level" ) ''PhyloLevel )
140 $(deriveJSON (unPrefix "_phylo_group" ) ''PhyloGroup )
142 $(deriveJSON (unPrefix "_software_" ) ''Software )
143 $(deriveJSON (unPrefix "_phyloParam_" ) ''PhyloParam )
144 $(deriveJSON (unPrefix "_phyloExport_" ) ''PhyloExport )
146 -- | TODO XML instances