Commit 13c81a8c authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Phylo][WIP] File Format parameters.

parent 08d3adb7
...@@ -28,6 +28,7 @@ one 8, e54847. ...@@ -28,6 +28,7 @@ one 8, e54847.
module Gargantext.Viz.Phylo where module Gargantext.Viz.Phylo where
import Control.Lens (makeLenses)
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Data.Text (Text) import Data.Text (Text)
...@@ -37,6 +38,28 @@ import Gargantext.Database.Schema.Ngrams (NgramsId) ...@@ -37,6 +38,28 @@ import Gargantext.Database.Schema.Ngrams (NgramsId)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude import Gargantext.Prelude
------------------------------------------------------------------------
data PhyloFormat =
PhyloFormat { _phyloFormat_parm :: PhyloParam
, _phyloFormat_data :: Phylo
} deriving (Generic)
-- | .phylo parameters
data PhyloParam =
PhyloParam { _phyloParam_version :: Text -- Double ?
, _phyloParam_software :: Software
, _phyloParam_params :: Hash
} deriving (Generic)
type Hash = Text
-- | Software
-- TODO move somewhere since it is generic
data Software =
Software { _software_name :: Text
, _software_version :: Text
} deriving (Generic)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Phylo datatype descriptor of a phylomemy -- | Phylo datatype descriptor of a phylomemy
-- Duration : time Segment of the whole phylomemy (start,end) -- Duration : time Segment of the whole phylomemy (start,end)
...@@ -103,8 +126,18 @@ type PhyloGroupId = (PhyloLevelId, Int) ...@@ -103,8 +126,18 @@ type PhyloGroupId = (PhyloLevelId, Int)
type Edge = (PhyloGroupId, Weight) type Edge = (PhyloGroupId, Weight)
type Weight = Double type Weight = Double
-- | Lenses
makeLenses ''Phylo
makeLenses ''PhyloParam
makeLenses ''PhyloFormat
makeLenses ''Software
-- | JSON instances -- | JSON instances
$(deriveJSON (unPrefix "_phylo_" ) ''Phylo ) $(deriveJSON (unPrefix "_phylo_" ) ''Phylo )
$(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod ) $(deriveJSON (unPrefix "_phylo_period" ) ''PhyloPeriod )
$(deriveJSON (unPrefix "_phylo_level" ) ''PhyloLevel ) $(deriveJSON (unPrefix "_phylo_level" ) ''PhyloLevel )
$(deriveJSON (unPrefix "_phylo_group" ) ''PhyloGroup ) $(deriveJSON (unPrefix "_phylo_group" ) ''PhyloGroup )
--
$(deriveJSON (unPrefix "_software_" ) ''Software )
$(deriveJSON (unPrefix "_phyloParam_" ) ''PhyloParam )
$(deriveJSON (unPrefix "_phyloFormat_" ) ''PhyloFormat )
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment