Phylo.hs 17.2 KB
Newer Older
1
{-|
2
Module      : Gargantext.Core.Viz.Phylo
3 4 5 6 7 8 9
Description : Phylomemy definitions and types.
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

10
Specifications of Phylomemy export format.
11 12 13 14 15 16 17

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).

18
References:
19 20 21 22 23 24
Chavalarias, D., Cointet, J.-P., 2013. Phylomemetic patterns
in science evolution — the rise and fall of scientific fields. PloS
one 8, e54847.

-}

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

28
module Gargantext.Core.Viz.Phylo where
29

30
import Control.DeepSeq
31
import Control.Lens (makeLenses)
32
import Data.Aeson.TH (deriveJSON,defaultOptions)
33
import Data.Map     (Map)
34
import Data.Set     (Set)
35
import Data.Swagger
36 37
import Data.Text    (Text)
import Data.Vector  (Vector)
38
import GHC.Generics (Generic)
39
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
40
import Gargantext.Prelude
41
import Gargantext.Core.Text.Context (TermList)
qlobbe's avatar
qlobbe committed
42

43 44 45 46 47 48
--------------------
-- | PhyloParam | --
--------------------


-- | Global parameters of a Phylo
49
data PhyloParam =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
50 51 52
     PhyloParam { _phyloParam_version  :: !Text -- Double ?
                , _phyloParam_software :: !Software
                , _phyloParam_query    :: !PhyloQueryBuild
53
     } deriving (Generic, Show, Eq)
54 55


56
-- | Software parameters
57
data Software =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
58 59
     Software { _software_name    :: !Text
              , _software_version :: !Text
60
     } deriving (Generic, Show, Eq)
61

62 63 64 65 66

---------------
-- | Phylo | --
---------------

Quentin Lobbé's avatar
Quentin Lobbé committed
67

68 69 70 71
-- | Phylo datatype of a phylomemy
-- Duration    : time Segment of the whole Phylo
-- Foundations : vector of all the Ngrams contained in a Phylo (build from a list of actants)
-- Periods     : list of all the periods of a Phylo
72
data Phylo =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
73 74
     Phylo { _phylo_duration    :: !(Start, End)
           , _phylo_foundations :: !PhyloFoundations
75
           , _phylo_periods     :: [PhyloPeriod]
Alexandre Delanoë's avatar
Alexandre Delanoë committed
76
           , _phylo_docsByYears :: !(Map Date Double)
77 78
           , _phylo_cooc        :: !(Map Date (Map (Int,Int) Double))
           , _phylo_fis         :: !(Map (Date,Date) [PhyloFis])
Alexandre Delanoë's avatar
Alexandre Delanoë committed
79
           , _phylo_param       :: !PhyloParam
80
           }
81
           deriving (Generic, Show, Eq)
82

83

84 85
-- | The foundations of a phylomemy created from a given TermList 
data PhyloFoundations =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
86 87
  PhyloFoundations { _phylo_foundationsRoots :: !(Vector Ngrams)
                   , _phylo_foundationsTermsList :: !TermList
88
  } deriving (Generic, Show, Eq)
Quentin Lobbé's avatar
Quentin Lobbé committed
89

90 91 92 93

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

94
-- | UTCTime in seconds since UNIX epoch
95 96
-- type Start   = POSIXTime
-- type End     = POSIXTime
97 98
type Start   = Date
type End     = Date
99

100 101 102 103 104 105

---------------------
-- | PhyloPeriod | --
---------------------


106 107 108 109
-- | PhyloStep : steps of phylomemy on temporal axis
-- Period: tuple (start date, end date) of the step of the phylomemy
-- Levels: levels of granularity
data PhyloPeriod =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
110 111
     PhyloPeriod { _phylo_periodId     :: !PhyloPeriodId
                 , _phylo_periodLevels :: ![PhyloLevel]
112
                 }
113
                 deriving (Generic, Show, Eq)
114 115


116 117 118 119 120
--------------------
-- | PhyloLevel | --
--------------------


121 122 123 124 125 126 127
-- | PhyloLevel : levels of phylomemy on level axis
-- Levels description:
-- Level -1: Ngram equals itself         (by identity) == _phylo_Ngrams
-- Level  0: Group of synonyms           (by stems + by qualitative expert meaning)
-- Level  1: First level of clustering
-- Level  N: Nth   level of clustering
data PhyloLevel =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
128 129
     PhyloLevel { _phylo_levelId     :: !PhyloLevelId
                , _phylo_levelGroups :: ![PhyloGroup]
130
                }
131
                deriving (Generic, Show, Eq)
132 133


134 135 136 137 138
--------------------
-- | PhyloGroup | --
--------------------


139 140 141
-- | PhyloGroup : group of ngrams at each level and step
-- Label : maybe has a label as text
-- Ngrams: set of terms that build the group
142
-- Quality : map of measures (support, etc.) that depict some qualitative aspects of a phylo
143 144
-- Period Parents|Childs: weighted link to Parents|Childs (Temporal Period   axis)
-- Level  Parents|Childs: weighted link to Parents|Childs (Level Granularity axis)
145
-- Pointers are directed link from Self to any PhyloGroup (/= Self ?)
146
data PhyloGroup =
Alexandre Delanoë's avatar
Alexandre Delanoë committed
147 148 149 150 151 152
     PhyloGroup { _phylo_groupId            :: !PhyloGroupId
                , _phylo_groupLabel         :: !Text
                , _phylo_groupNgrams        :: ![Int]
                , _phylo_groupNgramsMeta    :: !(Map Text [Double])
                , _phylo_groupMeta          :: !(Map Text Double)
                , _phylo_groupBranchId      :: !(Maybe PhyloBranchId)
153
                , _phylo_groupCooc          :: !(Map (Int,Int) Double)
154

Alexandre Delanoë's avatar
Alexandre Delanoë committed
155 156
                , _phylo_groupPeriodParents :: ![Pointer]
                , _phylo_groupPeriodChilds  :: ![Pointer]
157

Alexandre Delanoë's avatar
Alexandre Delanoë committed
158 159
                , _phylo_groupLevelParents  :: ![Pointer]
                , _phylo_groupLevelChilds   :: ![Pointer]
160
                }
qlobbe's avatar
qlobbe committed
161 162 163
                deriving (Generic, NFData, Show, Eq, Ord)

-- instance NFData PhyloGroup
164

Quentin Lobbé's avatar
Quentin Lobbé committed
165

166 167
-- | Level : A level of aggregation (-1 = Txt, 0 = Ngrams, 1 = Fis, [2..] = Cluster)
type Level = Int
Quentin Lobbé's avatar
Quentin Lobbé committed
168 169 170 171
-- | Index : A generic index of an element (PhyloGroup, PhyloBranch, etc) in a given List
type Index = Int


Quentin Lobbé's avatar
Quentin Lobbé committed
172
type PhyloPeriodId = (Start, End)
Quentin Lobbé's avatar
Quentin Lobbé committed
173 174 175
type PhyloLevelId  = (PhyloPeriodId, Level)
type PhyloGroupId  = (PhyloLevelId, Index)
type PhyloBranchId = (Level, Index)
176

Quentin Lobbé's avatar
Quentin Lobbé committed
177

Quentin Lobbé's avatar
Quentin Lobbé committed
178 179 180 181
-- | Weight : A generic mesure that can be associated with an Id
type Weight = Double
-- | Pointer : A weighted linked with a given PhyloGroup
type Pointer = (PhyloGroupId, Weight)
182 183 184 185
-- | Ngrams : a contiguous sequence of n terms
type Ngrams = Text


186
--------------------
187
-- | Aggregates | --
188
--------------------
Quentin Lobbé's avatar
Quentin Lobbé committed
189 190


191 192
-- | Document : a piece of Text linked to a Date
data Document = Document
Alexandre Delanoë's avatar
Alexandre Delanoë committed
193 194
      { date :: !Date
      , text :: ![Ngrams]
qlobbe's avatar
qlobbe committed
195
      } deriving (Show,Generic,NFData)
Quentin Lobbé's avatar
Quentin Lobbé committed
196

197 198 199
-- | Clique : Set of ngrams cooccurring in the same Document
type Clique   = Set Ngrams
-- | Support : Number of Documents where a Clique occurs
200 201 202
type Support  = Int
-- | Fis : Frequent Items Set (ie: the association between a Clique and a Support)
data PhyloFis = PhyloFis
Alexandre Delanoë's avatar
Alexandre Delanoë committed
203 204 205
  { _phyloFis_clique  :: !Clique
  , _phyloFis_support :: !Support
  , _phyloFis_period  :: !(Date,Date)
qlobbe's avatar
qlobbe committed
206
  } deriving (Generic,NFData,Show,Eq)
207

208
-- | A list of clustered PhyloGroup
209
type PhyloCluster = [PhyloGroup]
Quentin Lobbé's avatar
Quentin Lobbé committed
210 211


212 213 214 215
-- | A PhyloGroup in a Graph
type GroupNode  = PhyloGroup
-- | A weighted links between two PhyloGroups in a Graph
type GroupEdge  = ((PhyloGroup,PhyloGroup),Weight)
Quentin Lobbé's avatar
Quentin Lobbé committed
216
-- | The association as a Graph between a list of Nodes and a list of Edges
217
type GroupGraph = ([GroupNode],[GroupEdge])
Quentin Lobbé's avatar
Quentin Lobbé committed
218 219


220 221 222 223
---------------
-- | Error | --
---------------

224

225 226
data PhyloError = LevelDoesNotExist
                | LevelUnassigned
227
          deriving (Show)
228

229

230 231 232 233
-----------------
-- | Cluster | --
-----------------

234

235
-- | Cluster constructors
236
data Cluster = Fis FisParams
237 238
             | RelatedComponents RCParams
             | Louvain LouvainParams
239
        deriving (Generic, Show, Eq, Read)
240 241 242

-- | Parameters for Fis clustering
data FisParams = FisParams
Alexandre Delanoë's avatar
Alexandre Delanoë committed
243 244 245
  { _fis_keepMinorFis :: !Bool
  , _fis_minSupport   :: !Support
  , _fis_minSize      :: !Int
246
  } deriving (Generic, Show, Eq, Read)
247

248 249
-- | Parameters for RelatedComponents clustering
data RCParams = RCParams
Alexandre Delanoë's avatar
Alexandre Delanoë committed
250
  { _rc_proximity :: !Proximity } deriving (Generic, Show, Eq, Read)
Quentin Lobbé's avatar
Quentin Lobbé committed
251

252 253
-- | Parameters for Louvain clustering
data LouvainParams = LouvainParams
Alexandre Delanoë's avatar
Alexandre Delanoë committed
254
  { _louvain_proximity :: !Proximity } deriving (Generic, Show, Eq, Read)
Quentin Lobbé's avatar
Quentin Lobbé committed
255

256

257 258 259 260
-------------------
-- | Proximity | --
-------------------

261

262 263 264 265
-- | Proximity constructors
data Proximity = WeightedLogJaccard WLJParams
               | Hamming HammingParams
               | Filiation
266
          deriving (Generic, Show, Eq, Read)
267 268

-- | Parameters for WeightedLogJaccard proximity
269
data WLJParams = WLJParams
Alexandre Delanoë's avatar
Alexandre Delanoë committed
270 271
  { _wlj_threshold   :: !Double
  , _wlj_sensibility :: !Double
272
  } deriving (Generic, Show, Eq, Read)
Quentin Lobbé's avatar
Quentin Lobbé committed
273

274
-- | Parameters for Hamming proximity
275
data HammingParams = HammingParams
Alexandre Delanoë's avatar
Alexandre Delanoë committed
276
  { _hamming_threshold :: !Double } deriving (Generic, Show, Eq, Read)
Quentin Lobbé's avatar
Quentin Lobbé committed
277

278

279 280 281 282
----------------
-- | Filter | --
----------------

283

284
-- | Filter constructors
Quentin Lobbé's avatar
Quentin Lobbé committed
285 286 287
data Filter = LonelyBranch LBParams
            | SizeBranch SBParams
            deriving (Generic, Show, Eq)
288

Quentin Lobbé's avatar
Quentin Lobbé committed
289 290
-- | Parameters for LonelyBranch filter
data LBParams = LBParams
Alexandre Delanoë's avatar
Alexandre Delanoë committed
291 292 293
  { _lb_periodsInf :: !Int
  , _lb_periodsSup :: !Int
  , _lb_minNodes   :: !Int } deriving (Generic, Show, Eq)
Quentin Lobbé's avatar
Quentin Lobbé committed
294 295

-- | Parameters for SizeBranch filter
Quentin Lobbé's avatar
Quentin Lobbé committed
296
data SBParams = SBParams
Alexandre Delanoë's avatar
Alexandre Delanoë committed
297
  { _sb_minSize :: !Int } deriving (Generic, Show, Eq)
298

299

300
----------------
301
-- | Metric | --
302 303
----------------

304

305
-- | Metric constructors
306
data Metric = BranchAge | BranchBirth | BranchGroups deriving (Generic, Show, Eq, Read)
307

308

309 310 311 312
----------------
-- | Tagger | --
----------------

313

314
-- | Tagger constructors
qlobbe's avatar
qlobbe committed
315 316
data Tagger = BranchPeakFreq | BranchPeakCooc | BranchPeakInc
            | GroupLabelCooc | GroupLabelInc  | GroupLabelIncDyn deriving (Show,Generic,Read)
317

318

319 320 321 322
--------------
-- | Sort | --
--------------

323

324
-- | Sort constructors
qlobbe's avatar
qlobbe committed
325
data Sort  = ByBranchAge | ByBranchBirth deriving (Generic, Show, Read, Enum, Bounded)
326
data Order = Asc | Desc  deriving (Generic, Show, Read)
327

328

329 330 331 332
--------------------
-- | PhyloQuery | --
--------------------

333

334
-- | A Phyloquery describes a phylomemic reconstruction
335
data PhyloQueryBuild = PhyloQueryBuild
Alexandre Delanoë's avatar
Alexandre Delanoë committed
336 337
    { _q_phyloTitle :: !Text
    , _q_phyloDesc  :: !Text
Quentin Lobbé's avatar
Quentin Lobbé committed
338

339
    -- Grain and Steps for the PhyloPeriods
Alexandre Delanoë's avatar
Alexandre Delanoë committed
340 341
    , _q_periodGrain :: !Int
    , _q_periodSteps :: !Int
342 343

    -- Clustering method for building the contextual unit of Phylo (ie: level 1)
Alexandre Delanoë's avatar
Alexandre Delanoë committed
344 345 346
    , _q_contextualUnit :: !Cluster
    , _q_contextualUnitMetrics :: ![Metric]
    , _q_contextualUnitFilters :: ![Filter]
347

348
    -- Inter-temporal matching method of the Phylo
Alexandre Delanoë's avatar
Alexandre Delanoë committed
349 350 351
    , _q_interTemporalMatching :: !Proximity
    , _q_interTemporalMatchingFrame :: !Int
    , _q_interTemporalMatchingFrameTh :: !Double
352

Alexandre Delanoë's avatar
Alexandre Delanoë committed
353 354
    , _q_reBranchThr :: !Double
    , _q_reBranchNth :: !Int
qlobbe's avatar
qlobbe committed
355

356
    -- Last level of reconstruction
Alexandre Delanoë's avatar
Alexandre Delanoë committed
357
    , _q_nthLevel   :: !Level
358
    -- Clustering method used from level 1 to nthLevel
Alexandre Delanoë's avatar
Alexandre Delanoë committed
359
    , _q_nthCluster :: !Cluster
360
    } deriving (Generic, Show, Eq)
Quentin Lobbé's avatar
Quentin Lobbé committed
361

Quentin Lobbé's avatar
Quentin Lobbé committed
362
-- | To choose the Phylo edge you want to export : --> <-- <--> <=>
Quentin Lobbé's avatar
Quentin Lobbé committed
363
data Filiation = Ascendant | Descendant | Merge | Complete deriving (Generic, Show, Read)
Quentin Lobbé's avatar
Quentin Lobbé committed
364
data EdgeType  = PeriodEdge | LevelEdge deriving (Generic, Show, Eq)
Quentin Lobbé's avatar
Quentin Lobbé committed
365

366
-------------------
367
-- | PhyloView | --
368
-------------------
369

370

371
-- | A PhyloView is the output type of a Phylo
372
data PhyloView = PhyloView
Alexandre Delanoë's avatar
Alexandre Delanoë committed
373 374 375 376 377 378 379 380 381 382
  { _pv_param       :: !PhyloParam
  , _pv_title       :: !Text
  , _pv_description :: !Text
  , _pv_filiation   :: !Filiation
  , _pv_level       :: !Level
  , _pv_periods     :: ![PhyloPeriodId]
  , _pv_metrics     :: !(Map Text [Double])
  , _pv_branches    :: ![PhyloBranch]
  , _pv_nodes       :: ![PhyloNode]
  , _pv_edges       :: ![PhyloEdge]
383
  } deriving (Generic, Show)
384

385
-- | A phyloview is made of PhyloBranches, edges and nodes
386
data PhyloBranch = PhyloBranch
Alexandre Delanoë's avatar
Alexandre Delanoë committed
387 388 389
  { _pb_id      :: !PhyloBranchId
  , _pb_peak    :: !Text
  , _pb_metrics :: !(Map Text [Double])
390
  } deriving (Generic, Show)
391 392

data PhyloEdge = PhyloEdge
Alexandre Delanoë's avatar
Alexandre Delanoë committed
393 394 395 396
  { _pe_source :: !PhyloGroupId
  , _pe_target :: !PhyloGroupId
  , _pe_type   :: !EdgeType
  , _pe_weight :: !Weight
397
  } deriving (Generic, Show)
398 399

data PhyloNode = PhyloNode
Alexandre Delanoë's avatar
Alexandre Delanoë committed
400 401 402 403 404 405 406 407 408
  { _pn_id      :: !PhyloGroupId
  , _pn_bid     :: !(Maybe PhyloBranchId)
  , _pn_label   :: !Text
  , _pn_idx     :: ![Int]
  , _pn_ngrams  :: !(Maybe [Ngrams])
  , _pn_metrics :: !(Map Text [Double])
  , _pn_cooc    :: !(Map (Int,Int) Double)
  , _pn_parents :: !(Maybe [PhyloGroupId])
  , _pn_childs  :: ![PhyloNode]
409
  } deriving (Generic, Show)
410

411
------------------------
Quentin Lobbé's avatar
Quentin Lobbé committed
412
-- | PhyloQueryView | --
413
------------------------
414

415

416
data ExportMode = Json | Dot | Svg
Quentin Lobbé's avatar
Quentin Lobbé committed
417
  deriving (Generic, Show, Read)
418
data DisplayMode = Flat | Nested
419
  deriving (Generic, Show, Read)
420

421
-- | A PhyloQueryView describes a Phylo as an output view
422
data PhyloQueryView = PhyloQueryView
Alexandre Delanoë's avatar
Alexandre Delanoë committed
423
  { _qv_lvl    :: !Level
424

Quentin Lobbé's avatar
Quentin Lobbé committed
425
  -- Does the PhyloGraph contain ascendant, descendant or a complete Filiation ? Complet redondant et merge (avec le max)
Alexandre Delanoë's avatar
Alexandre Delanoë committed
426
  , _qv_filiation :: !Filiation
427 428

  -- Does the PhyloGraph contain some levelChilds ? How deep must it go ?
Alexandre Delanoë's avatar
Alexandre Delanoë committed
429 430
  , _qv_levelChilds      :: !Bool
  , _qv_levelChildsDepth :: !Level
431 432

  -- Ordered lists of filters, taggers and metrics to be applied to the PhyloGraph
433
  -- Firstly the metrics, then the filters and the taggers
Alexandre Delanoë's avatar
Alexandre Delanoë committed
434 435 436
  , _qv_metrics :: ![Metric]
  , _qv_filters :: ![Filter]
  , _qv_taggers :: ![Tagger]
437 438

  -- An asc or desc sort to apply to the PhyloGraph
Alexandre Delanoë's avatar
Alexandre Delanoë committed
439
  , _qv_sort :: !(Maybe (Sort,Order))
440

441
  -- A display mode to apply to the PhyloGraph, ie: [Node[Node,Edge],Edge] or [[Node,Node],[Edge,Edge]]
Alexandre Delanoë's avatar
Alexandre Delanoë committed
442 443 444
  , _qv_export  :: !ExportMode
  , _qv_display :: !DisplayMode
  , _qv_verbose :: !Bool
445 446
  }

447

448 449 450
----------------
-- | Lenses | --
----------------
451

452

453 454
makeLenses ''PhyloParam
makeLenses ''Software
455 456
--
makeLenses ''Phylo
457
makeLenses ''PhyloFoundations
458
makeLenses ''PhyloGroup
459 460
makeLenses ''PhyloLevel
makeLenses ''PhyloPeriod
461
makeLenses ''PhyloFis
462
--
463 464 465
makeLenses ''Proximity
makeLenses ''Cluster
makeLenses ''Filter
466
--
467
makeLenses ''PhyloQueryBuild
468
makeLenses ''PhyloQueryView
469 470
--
makeLenses ''PhyloView
471 472 473
makeLenses ''PhyloBranch
makeLenses ''PhyloNode
makeLenses ''PhyloEdge
474

475

476 477
------------------------
-- | JSON instances | --
478
------------------------
479

480

481
$(deriveJSON (unPrefix "_phylo_"       ) ''Phylo       )
482
$(deriveJSON (unPrefix "_phylo_foundations"  ) ''PhyloFoundations  )
483
$(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod )
484 485
$(deriveJSON (unPrefix "_phylo_level"  ) ''PhyloLevel  )
$(deriveJSON (unPrefix "_phylo_group"  ) ''PhyloGroup  )
486
$(deriveJSON (unPrefix "_phyloFis_"    ) ''PhyloFis    )
487
--
488
$(deriveJSON (unPrefix "_software_"    ) ''Software    )
489
$(deriveJSON (unPrefix "_phyloParam_"  ) ''PhyloParam  )
Quentin Lobbé's avatar
Quentin Lobbé committed
490
--
491 492
$(deriveJSON defaultOptions ''Filter    )
$(deriveJSON defaultOptions ''Metric    )
493 494 495 496 497 498 499 500
$(deriveJSON defaultOptions ''Cluster   )
$(deriveJSON defaultOptions ''Proximity )
--
$(deriveJSON (unPrefix "_fis_" )     ''FisParams     )
$(deriveJSON (unPrefix "_hamming_" ) ''HammingParams )
$(deriveJSON (unPrefix "_louvain_" ) ''LouvainParams )
$(deriveJSON (unPrefix "_rc_" )      ''RCParams      )
$(deriveJSON (unPrefix "_wlj_" )     ''WLJParams     )
Quentin Lobbé's avatar
Quentin Lobbé committed
501 502
--
$(deriveJSON (unPrefix "_lb_" )      ''LBParams      )
503
$(deriveJSON (unPrefix "_sb_" )      ''SBParams      )
504
--
505 506 507 508 509 510 511 512
$(deriveJSON (unPrefix "_q_" )  ''PhyloQueryBuild  )
$(deriveJSON (unPrefix "_pv_" ) ''PhyloView   )
$(deriveJSON (unPrefix "_pb_" ) ''PhyloBranch )
$(deriveJSON (unPrefix "_pe_" ) ''PhyloEdge   )
$(deriveJSON (unPrefix "_pn_" ) ''PhyloNode   )

$(deriveJSON defaultOptions ''Filiation )
$(deriveJSON defaultOptions ''EdgeType  )
513

514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564
---------------------------
-- | Swagger instances | --
---------------------------

instance ToSchema Phylo where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_")
instance ToSchema PhyloFoundations where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_foundations")
instance ToSchema PhyloPeriod where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_period")
instance ToSchema PhyloLevel where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_level")
instance ToSchema PhyloGroup where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phylo_group")
instance ToSchema PhyloFis where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phyloFis_")
instance ToSchema Software where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_software_")
instance ToSchema PhyloParam where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_phyloParam_")
instance ToSchema Filter
instance ToSchema Metric
instance ToSchema Cluster
instance ToSchema Proximity where
  declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions
instance ToSchema FisParams where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_fis_")
instance ToSchema HammingParams where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_hamming_")
instance ToSchema LouvainParams where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_louvain_")
instance ToSchema RCParams where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_rc_")
instance ToSchema WLJParams where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wlj_")
instance ToSchema LBParams where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_lb_")
instance ToSchema SBParams where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_sb_")
instance ToSchema PhyloQueryBuild where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_q_")
instance ToSchema PhyloView where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_pv_")
instance ToSchema PhyloBranch where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_pb_")
instance ToSchema PhyloEdge where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_pe_")
instance ToSchema PhyloNode where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_pn_")
instance ToSchema Filiation
instance ToSchema EdgeType
565

566 567 568
----------------------------
-- | TODO XML instances | --
----------------------------
Alexandre Delanoë's avatar
Alexandre Delanoë committed
569