]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Viz/Phylo.hs
[FIX] Typo.
[gargantext.git] / src / Gargantext / Viz / Phylo.hs
1 {-|
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
8 Portability : POSIX
9
10 Specifications of Phylomemy format.
11
12 Phylomemy can be described as a Temporal Graph with different scale of
13 granularity of group of ngrams (terms and multi-terms).
14
15 The main type is Phylo which is synonym of Phylomemy (only difference is
16 the number of chars).
17
18 References:
19 Chavalarias, D., Cointet, J.-P., 2013. Phylomemetic patterns
20 in science evolution — the rise and fall of scientific fields. PloS
21 one 8, e54847.
22
23 -}
24
25 {-# LANGUAGE DeriveGeneric #-}
26 {-# LANGUAGE NoImplicitPrelude #-}
27 {-# LANGUAGE TemplateHaskell #-}
28
29 module Gargantext.Viz.Phylo where
30
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
40
41 ------------------------------------------------------------------------
42 data PhyloFormat =
43 PhyloFormat { _phyloFormat_param :: PhyloParam
44 , _phyloFormat_data :: Phylo
45 } deriving (Generic)
46
47 -- | .phylo parameters
48 data PhyloParam =
49 PhyloParam { _phyloParam_version :: Text -- Double ?
50 , _phyloParam_software :: Software
51 , _phyloParam_params :: Hash
52 } deriving (Generic)
53
54 type Hash = Text
55
56 -- | Software
57 -- TODO move somewhere since it is generic
58 data Software =
59 Software { _software_name :: Text
60 , _software_version :: Text
61 } deriving (Generic)
62
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
68 data Phylo =
69 Phylo { _phylo_puration :: (Start, End)
70 , _phylo_ngrams :: [Ngram]
71 , _phylo_periods :: [PhyloPeriod]
72 }
73 deriving (Generic)
74
75 -- | UTCTime in seconds since UNIX epoch
76 type Start = POSIXTime
77 type End = POSIXTime
78
79 -- | Indexed Ngram
80 type Ngram = (NgramsId, Text)
81
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
85 data PhyloPeriod =
86 PhyloPeriod { _phylo_periodId :: PhyloPeriodId
87 , _phylo_periodLevels :: [PhyloLevel]
88 }
89 deriving (Generic)
90
91 type PhyloPeriodId = (Start, End)
92
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
99 data PhyloLevel =
100 PhyloLevel { _phylo_levelId :: PhyloLevelId
101 , _phylo_levelGroups :: [PhyloGroup]
102 }
103 deriving (Generic)
104
105 type PhyloLevelId = (PhyloPeriodId, Int)
106
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 data PhyloGroup =
113 PhyloGroup { _phylo_groupId :: PhyloGroupId
114 , _phylo_groupLabel :: Maybe Text
115 , _phylo_groupNgrams :: [NgramsId]
116
117 , _phylo_groupPeriodParents :: [Edge]
118 , _phylo_groupPeriodChilds :: [Edge]
119
120 , _phylo_groupLevelParents :: [Edge]
121 , _phylo_groupLevelChilds :: [Edge]
122 }
123 deriving (Generic)
124
125 type PhyloGroupId = (PhyloLevelId, Int)
126 type Edge = (PhyloGroupId, Weight)
127 type Weight = Double
128
129 -- | Lenses
130 makeLenses ''Phylo
131 makeLenses ''PhyloParam
132 makeLenses ''PhyloFormat
133 makeLenses ''Software
134
135 -- | JSON instances
136 $(deriveJSON (unPrefix "_phylo_" ) ''Phylo )
137 $(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod )
138 $(deriveJSON (unPrefix "_phylo_level" ) ''PhyloLevel )
139 $(deriveJSON (unPrefix "_phylo_group" ) ''PhyloGroup )
140 --
141 $(deriveJSON (unPrefix "_software_" ) ''Software )
142 $(deriveJSON (unPrefix "_phyloParam_" ) ''PhyloParam )
143 $(deriveJSON (unPrefix "_phyloFormat_" ) ''PhyloFormat )
144
145 -- | TODO XML instances
146