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)
37 import Data.Vector (Vector)
38 import Data.Time.Clock.POSIX (POSIXTime)
39 import GHC.Generics (Generic)
40 import Gargantext.Database.Schema.Ngrams (NgramsId)
41 import Gargantext.Core.Utils.Prefix (unPrefix)
42 import Gargantext.Prelude
44 ------------------------------------------------------------------------
46 PhyloExport { _phyloExport_param :: PhyloParam
47 , _phyloExport_data :: Phylo
50 -- | .phylo parameters
52 PhyloParam { _phyloParam_version :: Text -- Double ?
53 , _phyloParam_software :: Software
54 , _phyloParam_params :: Hash
60 -- TODO move somewhere since it is generic
62 Software { _software_name :: Text
63 , _software_version :: Text
66 ------------------------------------------------------------------------
67 -- | Phylo datatype descriptor of a phylomemy
68 -- Duration : time Segment of the whole phylomemy (start,end)
69 -- Ngrams : list of all (possible) terms contained in the phylomemy (with their id)
70 -- Steps : list of all steps to build the phylomemy
72 Phylo { _phylo_duration :: (Start, End)
73 , _phylo_ngrams :: PhyloNgrams
74 , _phylo_periods :: [PhyloPeriod]
76 deriving (Generic, Show)
79 -- | Date : a simple Integer
82 -- | UTCTime in seconds since UNIX epoch
83 -- type Start = POSIXTime
84 -- type End = POSIXTime
88 -- | PhyloStep : steps of phylomemy on temporal axis
89 -- Period: tuple (start date, end date) of the step of the phylomemy
90 -- Levels: levels of granularity
92 PhyloPeriod { _phylo_periodId :: PhyloPeriodId
93 , _phylo_periodLevels :: [PhyloLevel]
95 deriving (Generic, Show)
97 type PhyloPeriodId = (Start, End)
99 -- | PhyloLevel : levels of phylomemy on level axis
100 -- Levels description:
101 -- Level -1: Ngram equals itself (by identity) == _phylo_Ngrams
102 -- Level 0: Group of synonyms (by stems + by qualitative expert meaning)
103 -- Level 1: First level of clustering
104 -- Level N: Nth level of clustering
106 PhyloLevel { _phylo_levelId :: PhyloLevelId
107 , _phylo_levelGroups :: [PhyloGroup]
109 deriving (Generic, Show)
111 type PhyloLevelId = (PhyloPeriodId, Int)
113 -- | PhyloGroup : group of ngrams at each level and step
114 -- Label : maybe has a label as text
115 -- Ngrams: set of terms that build the group
116 -- Quality : map of measures (support, etc.) that depict some qualitative aspects of a phylo
117 -- Period Parents|Childs: weighted link to Parents|Childs (Temporal Period axis)
118 -- Level Parents|Childs: weighted link to Parents|Childs (Level Granularity axis)
119 -- Pointers are directed link from Self to any PhyloGroup (/= Self ?)
121 PhyloGroup { _phylo_groupId :: PhyloGroupId
122 , _phylo_groupLabel :: Text
123 , _phylo_groupNgrams :: [Int]
124 , _phylo_groupQuality :: Map Text Double
125 , _phylo_groupCooc :: Map (Int, Int) Double
127 , _phylo_groupPeriodParents :: [Pointer]
128 , _phylo_groupPeriodChilds :: [Pointer]
130 , _phylo_groupLevelParents :: [Pointer]
131 , _phylo_groupLevelChilds :: [Pointer]
133 deriving (Generic, Show, Eq)
135 type PhyloGroupId = (PhyloLevelId, Int)
136 type Pointer = (PhyloGroupId, Weight)
142 -- | Ngrams : a contiguous sequence of n terms
144 -- | PhyloNgrams : Vector of all the Ngrams (PhyloGroup of level -1) used within a Phylo
145 type PhyloNgrams = Vector Ngrams
148 -- | Clique : Set of ngrams cooccurring in the same Document
149 type Clique = Set Ngrams
150 -- | Support : Number of Documents where a Clique occurs
152 -- | Fis : Frequent Items Set (ie: the association between a Clique and a Support)
153 type Fis = Map Clique Support
156 data Direction = From | To
159 data LevelLabel = Level_m1 | Level_0 | Level_1 | Level_mN | Level_N | Level_pN
160 deriving (Show, Eq, Enum, Bounded)
163 Level { _levelLabel :: LevelLabel
168 LevelLink { _levelFrom :: Level
172 -- | Document : a piece of Text linked to a Date
173 data Document = Document
178 data PhyloError = LevelDoesNotExist
183 data Proximity = WeightedLogJaccard | Other
186 data PairTo = Childs | Parents
190 makeLenses ''PhyloParam
191 makeLenses ''PhyloExport
192 makeLenses ''Software
193 makeLenses ''PhyloGroup
194 makeLenses ''PhyloLevel
195 makeLenses ''PhyloPeriod
197 makeLenses ''LevelLink
200 $(deriveJSON (unPrefix "_phylo_" ) ''Phylo )
201 $(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod )
202 $(deriveJSON (unPrefix "_phylo_level" ) ''PhyloLevel )
203 $(deriveJSON (unPrefix "_phylo_group" ) ''PhyloGroup )
205 $(deriveJSON (unPrefix "_software_" ) ''Software )
206 $(deriveJSON (unPrefix "_phyloParam_" ) ''PhyloParam )
207 $(deriveJSON (unPrefix "_phyloExport_" ) ''PhyloExport )
209 -- | TODO XML instances