Phylo.hs 17.5 KB
Newer Older
qlobbe's avatar
qlobbe committed
1
{-
2
Module      : Gargantext.Core.Viz.AdaptativePhylo
3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23
Description : Phylomemy definitions and types.
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

Specifications of Phylomemy export format.

Phylomemy can be described as a Temporal Graph with different scale of
granularity of group of ngrams (terms and multi-terms).

The main type is Phylo which is synonym of Phylomemy (only difference is
the number of chars).

References:
Chavalarias, D., Cointet, J.-P., 2013. Phylomemetic patterns
in science evolution — the rise and fall of scientific fields. PloS
one 8, e54847.
-}

24
{-# LANGUAGE DeriveAnyClass   #-}
25 26
{-# LANGUAGE TemplateHaskell   #-}

27
module Gargantext.Core.Viz.Phylo where
28

qlobbe's avatar
qlobbe committed
29 30
import Data.Swagger
import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
31 32
import Control.DeepSeq (NFData)
import Control.Lens (makeLenses)
33 34
import Data.Aeson
import Data.Aeson.TH (deriveJSON)
35
import Data.Map (Map)
qlobbe's avatar
qlobbe committed
36
import Data.Text   (Text, pack)
37 38 39
import Data.Vector (Vector)
import GHC.Generics
import GHC.IO (FilePath)
40 41 42
import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude
43 44
import qualified Data.Text.Lazy as TextLazy

45 46
----------------
-- | Config | --
47
----------------
48

49
data CorpusParser =
qlobbe's avatar
qlobbe committed
50 51 52
      Wos  {_wos_limit  :: Int}
    | Csv  {_csv_limit  :: Int}
    | Csv' {_csv'_limit :: Int}
53
    deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
54

qlobbe's avatar
qlobbe committed
55 56 57 58 59 60 61 62
instance ToSchema CorpusParser where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_")


data ListParser = V3 | V4 deriving (Show,Generic,Eq)
instance ToSchema ListParser


63 64
data SeaElevation =
      Constante
65 66
      { _cons_start :: Double
      , _cons_step  :: Double }
67
    | Adaptative
68 69
      { _adap_granularity :: Double }
    deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
70

qlobbe's avatar
qlobbe committed
71 72
instance ToSchema SeaElevation

73 74
data Proximity =
      WeightedLogJaccard
75 76
      { _wlj_sensibility   :: Double
{-
77 78 79 80
      -- , _wlj_thresholdInit :: Double
      -- , _wlj_thresholdStep :: Double
      -- | max height for sea level in temporal matching
      -- , _wlj_elevation     :: Double
81
-}
82
      }
83
    | WeightedLogSim
84 85 86 87 88 89 90
      { _wlj_sensibility   :: Double
{-
      -- , _wlj_thresholdInit :: Double
      -- , _wlj_thresholdStep :: Double
      -- | max height for sea level in temporal matching
      -- , _wlj_elevation     :: Double
-}
91
      }
qlobbe's avatar
qlobbe committed
92 93
    | Hamming { _wlj_sensibility :: Double }

94
    deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
95

qlobbe's avatar
qlobbe committed
96 97 98 99 100 101
instance ToSchema Proximity where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")


data SynchronyScope = SingleBranch | SiblingBranches | AllBranches
  deriving (Show,Generic,Eq, ToSchema)
qlobbe's avatar
qlobbe committed
102

qlobbe's avatar
qlobbe committed
103 104 105 106 107
data SynchronyStrategy = MergeRegularGroups | MergeAllGroups
  deriving (Show,Generic,Eq)

instance ToSchema SynchronyStrategy where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
108 109


110
data Synchrony =
111
      ByProximityThreshold
112
      { _bpt_threshold :: Double
113 114 115
      , _bpt_sensibility :: Double
      , _bpt_scope :: SynchronyScope
      , _bpt_strategy :: SynchronyStrategy }
qlobbe's avatar
qlobbe committed
116
    | ByProximityDistribution
117
      { _bpd_sensibility :: Double
118 119
      , _bpd_strategy :: SynchronyStrategy }
    deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
120

qlobbe's avatar
qlobbe committed
121 122 123 124
instance ToSchema Synchrony where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_")


qlobbe's avatar
qlobbe committed
125

126
data TimeUnit =
qlobbe's avatar
qlobbe committed
127 128 129 130 131
      Epoch
      { _epoch_period :: Int
      , _epoch_step   :: Int
      , _epoch_matchingFrame :: Int }
    | Year
qlobbe's avatar
qlobbe committed
132 133 134
      { _year_period :: Int
      , _year_step   :: Int
      , _year_matchingFrame :: Int }
135
    | Month
qlobbe's avatar
qlobbe committed
136 137
      { _month_period :: Int
      , _month_step   :: Int
138 139
      , _month_matchingFrame :: Int }
    | Week
qlobbe's avatar
qlobbe committed
140 141 142
      { _week_period :: Int
      , _week_step   :: Int
      , _week_matchingFrame :: Int }
143
    | Day
qlobbe's avatar
qlobbe committed
144 145
      { _day_period :: Int
      , _day_step   :: Int
146 147
      , _day_matchingFrame :: Int }
      deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
148

qlobbe's avatar
qlobbe committed
149 150 151 152
instance ToSchema TimeUnit where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")


153
data CliqueFilter = ByThreshold | ByNeighbours deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
154

qlobbe's avatar
qlobbe committed
155 156 157 158 159
instance ToSchema CliqueFilter where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")



160 161
data Clique =
      Fis
qlobbe's avatar
qlobbe committed
162 163
      { _fis_support :: Int
      , _fis_size    :: Int }
164
    | MaxClique
165 166
      { _mcl_size      :: Int
      , _mcl_threshold :: Double
167 168
      , _mcl_filter    :: CliqueFilter }
      deriving (Show,Generic,Eq)
169

qlobbe's avatar
qlobbe committed
170 171 172
instance ToSchema Clique where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")

173

174
data Quality =
175 176
     Quality { _qua_granularity :: Double
             , _qua_minBranch   :: Int }
177
      deriving (Show,Generic,Eq)
178

qlobbe's avatar
qlobbe committed
179 180 181 182
instance ToSchema Quality where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_qua_")


qlobbe's avatar
qlobbe committed
183

184
data Config =
qlobbe's avatar
qlobbe committed
185 186 187 188
     Config { corpusPath     :: FilePath
            , listPath       :: FilePath
            , outputPath     :: FilePath
            , corpusParser   :: CorpusParser
qlobbe's avatar
qlobbe committed
189
            , listParser     :: ListParser
qlobbe's avatar
qlobbe committed
190 191 192
            , phyloName      :: Text
            , phyloLevel     :: Int
            , phyloProximity :: Proximity
193
            , seaElevation   :: SeaElevation
194
            , findAncestors  :: Bool
qlobbe's avatar
qlobbe committed
195
            , phyloSynchrony :: Synchrony
196
            , phyloQuality   :: Quality
qlobbe's avatar
qlobbe committed
197
            , timeUnit       :: TimeUnit
198
            , clique         :: Clique
qlobbe's avatar
qlobbe committed
199 200
            , exportLabel    :: [PhyloLabel]
            , exportSort     :: Sort
201
            , exportFilter   :: [Filter]
qlobbe's avatar
qlobbe committed
202 203
            } deriving (Show,Generic,Eq)

qlobbe's avatar
qlobbe committed
204 205
instance ToSchema Config

qlobbe's avatar
qlobbe committed
206

207
defaultConfig :: Config
208
defaultConfig =
qlobbe's avatar
qlobbe committed
209 210 211 212 213 214
     Config { corpusPath     = "corpus.csv" -- useful for commandline only
            , listPath       = "list.csv"   -- useful for commandline only
            , outputPath     = "data/"
            , corpusParser   = Csv 100000
            , listParser     = V4
            , phyloName      = pack "Phylo Name"
qlobbe's avatar
qlobbe committed
215
            , phyloLevel     = 2
qlobbe's avatar
qlobbe committed
216
            , phyloProximity = WeightedLogJaccard 0.5
qlobbe's avatar
qlobbe committed
217
            , seaElevation   = Constante 0.1 0.1
qlobbe's avatar
qlobbe committed
218 219 220
            , findAncestors  = False
            , phyloSynchrony = ByProximityThreshold 0.5 0 AllBranches MergeAllGroups
            , phyloQuality   = Quality 0.5 1
qlobbe's avatar
qlobbe committed
221
            , timeUnit       = Year 3 1 5
qlobbe's avatar
qlobbe committed
222
            , clique         = MaxClique 5 0.0001 ByThreshold
qlobbe's avatar
qlobbe committed
223
            , exportLabel    = [BranchLabel MostEmergentTfIdf 2, GroupLabel MostEmergentInclusive 2]
qlobbe's avatar
qlobbe committed
224 225
            , exportSort     = ByHierarchy Desc
            , exportFilter   = [ByBranchSize 3]
qlobbe's avatar
qlobbe committed
226
            }
227 228 229

instance FromJSON Config
instance ToJSON Config
230

231 232
instance FromJSON CorpusParser
instance ToJSON CorpusParser
233

qlobbe's avatar
qlobbe committed
234 235 236
instance FromJSON ListParser
instance ToJSON ListParser

qlobbe's avatar
qlobbe committed
237 238
instance FromJSON Proximity
instance ToJSON Proximity
239

240 241
instance FromJSON SeaElevation
instance ToJSON SeaElevation
242

qlobbe's avatar
qlobbe committed
243 244
instance FromJSON TimeUnit
instance ToJSON TimeUnit
245

246 247
instance FromJSON CliqueFilter
instance ToJSON CliqueFilter
248

249 250
instance FromJSON Clique
instance ToJSON Clique
251

qlobbe's avatar
qlobbe committed
252 253
instance FromJSON PhyloLabel
instance ToJSON PhyloLabel
254

255 256
instance FromJSON Tagger
instance ToJSON Tagger
257

qlobbe's avatar
qlobbe committed
258 259
instance FromJSON Sort
instance ToJSON Sort
260

qlobbe's avatar
qlobbe committed
261 262
instance FromJSON Order
instance ToJSON Order
263

qlobbe's avatar
qlobbe committed
264 265
instance FromJSON Filter
instance ToJSON Filter
266

267 268
instance FromJSON SynchronyScope
instance ToJSON SynchronyScope
269

270 271
instance FromJSON SynchronyStrategy
instance ToJSON SynchronyStrategy
272

qlobbe's avatar
qlobbe committed
273 274
instance FromJSON Synchrony
instance ToJSON Synchrony
275

276 277
instance FromJSON Quality
instance ToJSON Quality
278 279


qlobbe's avatar
qlobbe committed
280 281 282 283 284 285
-- | Software parameters
data Software =
     Software { _software_name    :: Text
              , _software_version :: Text
     } deriving (Generic, Show, Eq)

qlobbe's avatar
qlobbe committed
286 287 288 289 290
instance ToSchema Software where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_software_")



291
defaultSoftware :: Software
292
defaultSoftware =
qlobbe's avatar
qlobbe committed
293 294 295 296 297 298 299 300 301 302 303
      Software { _software_name    = pack "Gargantext"
               , _software_version = pack "v4" }


-- | Global parameters of a Phylo
data PhyloParam =
     PhyloParam { _phyloParam_version  :: Text
                , _phyloParam_software :: Software
                , _phyloParam_config   :: Config
     } deriving (Generic, Show, Eq)

qlobbe's avatar
qlobbe committed
304 305 306 307 308
instance ToSchema PhyloParam where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phyloParam_")



309
defaultPhyloParam :: PhyloParam
qlobbe's avatar
qlobbe committed
310 311 312 313 314 315
defaultPhyloParam =
      PhyloParam { _phyloParam_version  = pack "v2.adaptative"
                 , _phyloParam_software = defaultSoftware
                 , _phyloParam_config   = defaultConfig }


316 317 318 319 320 321 322 323 324 325
------------------
-- | Document | --
------------------

-- | Date : a simple Integer
type Date = Int

-- | Ngrams : a contiguous sequence of n terms
type Ngrams = Text

qlobbe's avatar
qlobbe committed
326 327
-- Document : a piece of Text linked to a Date
-- date = computational date; date' = original string date yyyy-mm-dd
328
-- Export Database to Document
329
data Document = Document
330 331
      { date    :: Date   -- datatype Date {unDate :: Int}
      , date'   :: Text   -- show date
qlobbe's avatar
qlobbe committed
332 333 334
      , text    :: [Ngrams]
      , weight  :: Maybe Double
      , sources :: [Text]
335
      } deriving (Eq,Show,Generic,NFData)
336 337 338 339 340 341 342


--------------------
-- | Foundation | --
--------------------


343
-- | The Foundations of a Phylo created from a given TermList
344 345 346 347 348
data PhyloFoundations = PhyloFoundations
      { _foundations_roots   :: !(Vector Ngrams)
      , _foundations_mapList :: TermList
      } deriving (Generic, Show, Eq)

qlobbe's avatar
qlobbe committed
349 350 351 352
instance ToSchema PhyloFoundations where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_foundations_")


353

qlobbe's avatar
qlobbe committed
354 355 356
data PhyloSources = PhyloSources
      { _sources :: !(Vector Text) } deriving (Generic, Show, Eq)

qlobbe's avatar
qlobbe committed
357 358
instance ToSchema PhyloSources where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_")
qlobbe's avatar
qlobbe committed
359

qlobbe's avatar
qlobbe committed
360 361 362 363 364
---------------------------
-- | Coocurency Matrix | --
---------------------------


365 366
-- | Cooc : a coocurency matrix between two ngrams
type Cooc =  Map (Int,Int) Double
qlobbe's avatar
qlobbe committed
367 368 369 370 371 372 373 374 375 376 377 378


-------------------
-- | Phylomemy | --
-------------------


-- | Phylo datatype of a phylomemy
--  foundations : the foundations of the phylo
--  timeCooc : a Map of coocurency by minimal unit of time (ex: by year)
--  timeDocs : a Map with the numbers of docs by minimal unit of time (ex: by year)
--  param : the parameters of the phylomemy (with the user's configuration)
379
--  periods : the temporal steps of a phylomemy
qlobbe's avatar
qlobbe committed
380
data Phylo =
qlobbe's avatar
qlobbe committed
381
     Phylo { _phylo_foundations  :: PhyloFoundations
qlobbe's avatar
qlobbe committed
382
           , _phylo_sources      :: PhyloSources
qlobbe's avatar
qlobbe committed
383 384 385
           , _phylo_timeCooc     :: !(Map Date Cooc)
           , _phylo_timeDocs     :: !(Map Date Double)
           , _phylo_termFreq     :: !(Map Int Double)
386 387
           , _phylo_lastTermFreq :: !(Map Int Double)
           , _phylo_horizon      :: !(Map (PhyloGroupId,PhyloGroupId) Double)
qlobbe's avatar
qlobbe committed
388 389 390
           , _phylo_groupsProxi  :: !(Map (PhyloGroupId,PhyloGroupId) Double)
           , _phylo_param        :: PhyloParam
           , _phylo_periods      :: Map PhyloPeriodId PhyloPeriod
qlobbe's avatar
qlobbe committed
391 392 393
           }
           deriving (Generic, Show, Eq)

qlobbe's avatar
qlobbe committed
394 395 396
instance ToSchema Phylo where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_")

qlobbe's avatar
qlobbe committed
397

398 399 400 401 402 403 404
-- | PhyloPeriodId : the id of a given period
type PhyloPeriodId = (Date,Date)

-- | PhyloPeriod : steps of a phylomemy on a temporal axis
--  id: tuple (start date, end date) of the temporal step of the phylomemy
--  levels: levels of granularity
data PhyloPeriod =
qlobbe's avatar
qlobbe committed
405 406 407
     PhyloPeriod { _phylo_periodPeriod  :: (Date,Date)
                 , _phylo_periodPeriod' :: (Text,Text)
                 , _phylo_periodLevels  :: Map PhyloLevelId PhyloLevel
408
                 } deriving (Generic, Show, Eq)
409

qlobbe's avatar
qlobbe committed
410 411 412 413
instance ToSchema PhyloPeriod where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_")


414 415 416 417

-- | Level : a level of clustering
type Level = Int

418
-- | PhyloLevelId : the id of a level of clustering in a given period
419 420 421 422 423 424 425 426
type PhyloLevelId  = (PhyloPeriodId,Level)

-- | PhyloLevel : levels of phylomemy on a synchronic axis
-- Levels description:
-- Level 0: The foundations and the base of the phylo
-- Level 1: First level of clustering (the Fis)
-- Level [2..N]: Nth level of synchronic clustering (cluster of Fis)
data PhyloLevel =
qlobbe's avatar
qlobbe committed
427 428
     PhyloLevel { _phylo_levelPeriod  :: (Date,Date)
                , _phylo_levelPeriod' :: (Text,Text)
429
                , _phylo_levelLevel   :: Level
qlobbe's avatar
qlobbe committed
430
                , _phylo_levelGroups  :: Map PhyloGroupId PhyloGroup
431 432
                }
                deriving (Generic, Show, Eq)
433

qlobbe's avatar
qlobbe committed
434 435 436
instance ToSchema PhyloLevel where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_")

437

qlobbe's avatar
qlobbe committed
438
type PhyloGroupId  = (PhyloLevelId, Int)
439

qlobbe's avatar
qlobbe committed
440 441 442
-- | BranchId : (a level, a sequence of branch index)
-- the sequence is a path of heritage from the most to the less specific branch
type PhyloBranchId = (Level, [Int])
443 444

-- | PhyloGroup : group of ngrams at each level and period
445
data PhyloGroup =
qlobbe's avatar
qlobbe committed
446
      PhyloGroup { _phylo_groupPeriod   :: (Date,Date)
qlobbe's avatar
qlobbe committed
447
                 , _phylo_groupPeriod'  :: (Text,Text)
qlobbe's avatar
qlobbe committed
448
                 , _phylo_groupLevel    :: Level
449
                 , _phylo_groupIndex    :: Int
450
                 , _phylo_groupLabel    :: Text
qlobbe's avatar
qlobbe committed
451
                 , _phylo_groupSupport  :: Support
qlobbe's avatar
qlobbe committed
452
                 , _phylo_groupWeight   :: Maybe Double
453
                 , _phylo_groupSources  :: [Int]
qlobbe's avatar
qlobbe committed
454
                 , _phylo_groupNgrams   :: [Int]
qlobbe's avatar
qlobbe committed
455
                 , _phylo_groupCooc     :: !(Cooc)
qlobbe's avatar
qlobbe committed
456
                 , _phylo_groupBranchId :: PhyloBranchId
457
                 , _phylo_groupMeta     :: Map Text [Double]
qlobbe's avatar
qlobbe committed
458 459 460 461
                 , _phylo_groupLevelParents  :: [Pointer]
                 , _phylo_groupLevelChilds   :: [Pointer]
                 , _phylo_groupPeriodParents :: [Pointer]
                 , _phylo_groupPeriodChilds  :: [Pointer]
qlobbe's avatar
qlobbe committed
462
                 , _phylo_groupAncestors     :: [Pointer]
qlobbe's avatar
qlobbe committed
463 464
                 , _phylo_groupPeriodMemoryParents :: [Pointer']
                 , _phylo_groupPeriodMemoryChilds  :: [Pointer']
465
                 }
qlobbe's avatar
qlobbe committed
466
                 deriving (Generic, Show, Eq, NFData)
467

qlobbe's avatar
qlobbe committed
468 469 470 471
instance ToSchema PhyloGroup where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_")


qlobbe's avatar
qlobbe committed
472 473
-- | Weight : A generic mesure that can be associated with an Id
type Weight = Double
qlobbe's avatar
qlobbe committed
474
type Thr = Double
qlobbe's avatar
qlobbe committed
475 476

-- | Pointer : A weighted pointer to a given PhyloGroup
qlobbe's avatar
qlobbe committed
477
type Pointer = (PhyloGroupId, Weight)
qlobbe's avatar
qlobbe committed
478 479
-- | Pointer' : A weighted pointer to a given PhyloGroup with a lower bounded threshold
type Pointer' = (PhyloGroupId, (Thr,Weight))
qlobbe's avatar
qlobbe committed
480

qlobbe's avatar
qlobbe committed
481
data Filiation = ToParents | ToChilds | ToParentsMemory | ToChildsMemory deriving (Generic, Show)
482
data PointerType = TemporalPointer | LevelPointer deriving (Generic, Show)
qlobbe's avatar
qlobbe committed
483

484

485 486 487
----------------------
-- | Phylo Clique | --
----------------------
488 489 490 491

-- | Support : Number of Documents where a Clique occurs
type Support  = Int

492
data PhyloClique = PhyloClique
qlobbe's avatar
qlobbe committed
493
  { _phyloClique_nodes   :: [Int]
494 495
  , _phyloClique_support :: Support
  , _phyloClique_period  :: (Date,Date)
qlobbe's avatar
qlobbe committed
496
  , _phyloClique_weight  :: Maybe Double
qlobbe's avatar
qlobbe committed
497
  , _phyloClique_sources :: [Int]
498 499
  } deriving (Generic,NFData,Show,Eq)

500 501 502 503 504 505
----------------
-- | Export | --
----------------

type DotId = TextLazy.Text

qlobbe's avatar
qlobbe committed
506
data EdgeType = GroupToGroup | GroupToGroupMemory | BranchToGroup | BranchToBranch | GroupToAncestor | PeriodToPeriod deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
507

qlobbe's avatar
qlobbe committed
508
data Filter = ByBranchSize { _branch_size :: Double } deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
509 510 511 512 513
instance ToSchema Filter where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")


data Order = Asc | Desc deriving (Show,Generic,Eq, ToSchema)
qlobbe's avatar
qlobbe committed
514

qlobbe's avatar
qlobbe committed
515 516 517
data Sort = ByBirthDate { _sort_order :: Order } | ByHierarchy {_sort_order :: Order } deriving (Show,Generic,Eq)
instance ToSchema Sort where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_sort_")
qlobbe's avatar
qlobbe committed
518 519


qlobbe's avatar
qlobbe committed
520
data Tagger = MostInclusive | MostEmergentInclusive | MostEmergentTfIdf deriving (Show,Generic,Eq)
qlobbe's avatar
qlobbe committed
521 522 523
instance ToSchema Tagger where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")

524

525
data PhyloLabel =
526 527 528 529 530 531 532 533
      BranchLabel
      { _branch_labelTagger :: Tagger
      , _branch_labelSize   :: Int }
    | GroupLabel
      { _group_labelTagger  :: Tagger
      , _group_labelSize    :: Int }
    deriving (Show,Generic,Eq)

qlobbe's avatar
qlobbe committed
534 535 536 537
instance ToSchema PhyloLabel where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_")


538 539 540
data PhyloBranch =
      PhyloBranch
      { _branch_id :: PhyloBranchId
541 542 543 544
      , _branch_canonId  :: [Int]
      , _branch_seaLevel :: [Double]
      , _branch_x        :: Double
      , _branch_y        :: Double
qlobbe's avatar
qlobbe committed
545 546
      , _branch_w        :: Double
      , _branch_t        :: Double
547 548 549
      , _branch_label    :: Text
      , _branch_meta     :: Map Text [Double]
      } deriving (Generic, Show, Eq)
550

qlobbe's avatar
qlobbe committed
551 552 553
instance ToSchema PhyloBranch where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_branch_")

554 555
data PhyloExport =
      PhyloExport
qlobbe's avatar
qlobbe committed
556 557
      { _export_groups    :: [PhyloGroup]
      , _export_branches  :: [PhyloBranch]
558
      } deriving (Generic, Show)
qlobbe's avatar
qlobbe committed
559 560 561
instance ToSchema PhyloExport where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_export_")

562

563 564 565 566
----------------
-- | Lenses | --
----------------

qlobbe's avatar
qlobbe committed
567
makeLenses ''Config
qlobbe's avatar
qlobbe committed
568
makeLenses ''Proximity
569
makeLenses ''SeaElevation
570
makeLenses ''Quality
571
makeLenses ''Clique
qlobbe's avatar
qlobbe committed
572
makeLenses ''PhyloLabel
qlobbe's avatar
qlobbe committed
573
makeLenses ''TimeUnit
574
makeLenses ''PhyloFoundations
575
makeLenses ''PhyloClique
576 577 578 579 580
makeLenses ''Phylo
makeLenses ''PhyloPeriod
makeLenses ''PhyloLevel
makeLenses ''PhyloGroup
makeLenses ''PhyloParam
581 582
makeLenses ''PhyloExport
makeLenses ''PhyloBranch
583 584 585 586 587

------------------------
-- | JSON instances | --
------------------------

qlobbe's avatar
qlobbe committed
588 589
instance FromJSON Phylo
instance ToJSON Phylo
590

qlobbe's avatar
qlobbe committed
591 592
instance FromJSON PhyloSources
instance ToJSON PhyloSources
593

qlobbe's avatar
qlobbe committed
594 595
instance FromJSON PhyloParam
instance ToJSON PhyloParam
596

qlobbe's avatar
qlobbe committed
597 598
instance FromJSON PhyloPeriod
instance ToJSON PhyloPeriod
599

qlobbe's avatar
qlobbe committed
600 601
instance FromJSON PhyloLevel
instance ToJSON PhyloLevel
602

qlobbe's avatar
qlobbe committed
603 604
instance FromJSON Software
instance ToJSON Software
605

qlobbe's avatar
qlobbe committed
606 607
instance FromJSON PhyloGroup
instance ToJSON PhyloGroup
608

609
$(deriveJSON (unPrefix "_foundations_"  ) ''PhyloFoundations)