Commit c7ae5797 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT][PHYLO] update parameters with PhyloSubConfig

parent 24a13986
...@@ -136,7 +136,7 @@ fileToDocs' parser path time lst = do ...@@ -136,7 +136,7 @@ fileToDocs' parser path time lst = do
-- Config time parameters to label -- Config time parameters to label
timeToLabel :: Config -> [Char] timeToLabel :: PhyloConfig -> [Char]
timeToLabel config = case (timeUnit config) of timeToLabel config = case (timeUnit config) of
Epoch p s f -> ("time_epochs" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f)) Epoch p s f -> ("time_epochs" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f))
Year p s f -> ("time_years" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f)) Year p s f -> ("time_years" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f))
...@@ -145,37 +145,37 @@ timeToLabel config = case (timeUnit config) of ...@@ -145,37 +145,37 @@ timeToLabel config = case (timeUnit config) of
Day p s f -> ("time_days" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f)) Day p s f -> ("time_days" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f))
seaToLabel :: Config -> [Char] seaToLabel :: PhyloConfig -> [Char]
seaToLabel config = case (seaElevation config) of seaToLabel config = case (seaElevation config) of
Constante start step -> ("sea_cst_" <> (show start) <> "_" <> (show step)) Constante start step -> ("sea_cst_" <> (show start) <> "_" <> (show step))
Adaptative granularity -> ("sea_adapt" <> (show granularity)) Adaptative granularity -> ("sea_adapt" <> (show granularity))
sensToLabel :: Config -> [Char] sensToLabel :: PhyloConfig -> [Char]
sensToLabel config = case (phyloProximity config) of sensToLabel config = case (phyloProximity config) of
Hamming _ -> undefined Hamming _ -> undefined
WeightedLogJaccard s -> ("WeightedLogJaccard_" <> show s) WeightedLogJaccard s -> ("WeightedLogJaccard_" <> show s)
WeightedLogSim s -> ( "WeightedLogSim-sens_" <> show s) WeightedLogSim s -> ( "WeightedLogSim-sens_" <> show s)
cliqueToLabel :: Config -> [Char] cliqueToLabel :: PhyloConfig -> [Char]
cliqueToLabel config = case (clique config) of cliqueToLabel config = case (clique config) of
Fis s s' -> "fis_" <> (show s) <> "_" <> (show s') Fis s s' -> "fis_" <> (show s) <> "_" <> (show s')
MaxClique s t f -> "clique_" <> (show s)<> "_" <> (show f)<> "_" <> (show t) MaxClique s t f -> "clique_" <> (show s)<> "_" <> (show f)<> "_" <> (show t)
syncToLabel :: Config -> [Char] syncToLabel :: PhyloConfig -> [Char]
syncToLabel config = case (phyloSynchrony config) of syncToLabel config = case (phyloSynchrony config) of
ByProximityThreshold scl sync_sens scope _ -> ("scale_" <> (show scope) <> "_" <> (show sync_sens) <> "_" <> (show scl)) ByProximityThreshold scl sync_sens scope _ -> ("scale_" <> (show scope) <> "_" <> (show sync_sens) <> "_" <> (show scl))
ByProximityDistribution _ _ -> undefined ByProximityDistribution _ _ -> undefined
qualToConfig :: Config -> [Char] qualToConfig :: PhyloConfig -> [Char]
qualToConfig config = case (phyloQuality config) of qualToConfig config = case (phyloQuality config) of
Quality g m -> "quality_" <> (show g) <> "_" <> (show m) Quality g m -> "quality_" <> (show g) <> "_" <> (show m)
-- To set up the export file's label from the configuration -- To set up the export file's label from the configuration
configToLabel :: Config -> [Char] configToLabel :: PhyloConfig -> [Char]
configToLabel config = outputPath config configToLabel config = outputPath config
<> (unpack $ phyloName config) <> (unpack $ phyloName config)
<> "-" <> (timeToLabel config) <> "-" <> (timeToLabel config)
...@@ -189,7 +189,7 @@ configToLabel config = outputPath config ...@@ -189,7 +189,7 @@ configToLabel config = outputPath config
-- To write a sha256 from a set of config's parameters -- To write a sha256 from a set of config's parameters
configToSha :: PhyloStage -> Config -> [Char] configToSha :: PhyloStage -> PhyloConfig -> [Char]
configToSha stage config = unpack configToSha stage config = unpack
$ replace "/" "-" $ replace "/" "-"
$ T.pack (show (hash $ C8.pack label)) $ T.pack (show (hash $ C8.pack label))
...@@ -242,7 +242,7 @@ main = do ...@@ -242,7 +242,7 @@ main = do
printIOMsg "Read the configuration file" printIOMsg "Read the configuration file"
[args] <- getArgs [args] <- getArgs
jsonArgs <- (eitherDecode <$> readJson args) :: IO (Either String Config) jsonArgs <- (eitherDecode <$> readJson args) :: IO (Either String PhyloConfig)
case jsonArgs of case jsonArgs of
Left err -> putStrLn err Left err -> putStrLn err
......
...@@ -29,12 +29,14 @@ import Gargantext.Core.Methods.Distances (GraphMetric(..)) ...@@ -29,12 +29,14 @@ import Gargantext.Core.Methods.Distances (GraphMetric(..))
import Gargantext.Core.Types.Main (ListType(..)) import Gargantext.Core.Types.Main (ListType(..))
import Gargantext.Core.Viz.Graph.API (recomputeGraph) import Gargantext.Core.Viz.Graph.API (recomputeGraph)
import Gargantext.Core.Viz.Graph.Tools (PartitionMethod(..)) import Gargantext.Core.Viz.Graph.Tools (PartitionMethod(..))
import Gargantext.Core.Viz.Phylo (PhyloSubConfig(..), subConfig2config)
import Gargantext.Core.Viz.Phylo.API.Tools (flowPhyloAPI)
import Gargantext.Database.Action.Flow.Pairing (pairing) import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Action.Metrics (updateNgramsOccurrences, updateContextScore) import Gargantext.Database.Action.Metrics (updateNgramsOccurrences, updateContextScore)
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Query.Table.Node (defaultList) import Gargantext.Database.Query.Table.Node (defaultList, getNode, insertNodes, node)
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Schema.Ngrams (NgramsType(NgramsTerms)) import Gargantext.Database.Schema.Ngrams (NgramsType(NgramsTerms))
import Gargantext.Database.Schema.Node (node_parent_id) import Gargantext.Database.Schema.Node (node_parent_id)
import Gargantext.Prelude (Bool(..), Ord, Eq, (<$>), ($), liftBase, (.), printDebug, pure, show, cs, (<>), panic, (<*>)) import Gargantext.Prelude (Bool(..), Ord, Eq, (<$>), ($), liftBase, (.), printDebug, pure, show, cs, (<>), panic, (<*>))
...@@ -54,12 +56,19 @@ type API = Summary " Update node according to NodeType params" ...@@ -54,12 +56,19 @@ type API = Summary " Update node according to NodeType params"
------------------------------------------------------------------------ ------------------------------------------------------------------------
data UpdateNodeParams = UpdateNodeParamsList { methodList :: !Method } data UpdateNodeParams = UpdateNodeParamsList { methodList :: !Method }
| UpdateNodeParamsGraph { methodGraphMetric :: !GraphMetric | UpdateNodeParamsGraph { methodGraphMetric :: !GraphMetric
, methodGraphClustering :: !PartitionMethod , methodGraphClustering :: !PartitionMethod
} }
| UpdateNodeParamsTexts { methodTexts :: !Granularity } | UpdateNodeParamsTexts { methodTexts :: !Granularity }
| UpdateNodeParamsBoard { methodBoard :: !Charts } | UpdateNodeParamsBoard { methodBoard :: !Charts }
| LinkNodeReq { nodeType :: !NodeType, id :: !NodeId }
| LinkNodeReq { nodeType :: !NodeType
, id :: !NodeId }
| UpdateNodePhylo { config :: !PhyloSubConfig }
deriving (Generic) deriving (Generic)
---------------------------------------------------------------------- ----------------------------------------------------------------------
...@@ -182,6 +191,34 @@ updateNode _uId lId (UpdateNodeParamsList _mode) logStatus = do ...@@ -182,6 +191,34 @@ updateNode _uId lId (UpdateNodeParamsList _mode) logStatus = do
, _scst_events = Just [] , _scst_events = Just []
} }
updateNode userId phyloId (UpdateNodePhylo config) logStatus = do
logStatus JobLog { _scst_succeeded = Just 1
, _scst_failed = Just 0
, _scst_remaining = Just 2
, _scst_events = Just []
}
corpusId' <- view node_parent_id <$> getNode phyloId
let corpusId = fromMaybe (panic "") corpusId'
phy <- flowPhyloAPI (subConfig2config config) corpusId
logStatus JobLog { _scst_succeeded = Just 2
, _scst_failed = Just 0
, _scst_remaining = Just 1
, _scst_events = Just []
}
_phyloId <- insertNodes [node NodePhylo "Phylo" (HyperdataPhylo Nothing (Just phy)) (Just corpusId) userId]
pure JobLog { _scst_succeeded = Just 3
, _scst_failed = Just 0
, _scst_remaining = Just 0
, _scst_events = Just []
}
updateNode _uId tId (UpdateNodeParamsTexts _mode) logStatus = do updateNode _uId tId (UpdateNodeParamsTexts _mode) logStatus = do
logStatus JobLog { _scst_succeeded = Just 1 logStatus JobLog { _scst_succeeded = Just 1
, _scst_failed = Just 0 , _scst_failed = Just 0
......
...@@ -101,8 +101,9 @@ getGraph _uId nId = do ...@@ -101,8 +101,9 @@ getGraph _uId nId = do
-- TODO Distance in Graph params -- TODO Distance in Graph params
case graph of case graph of
Nothing -> do Nothing -> do
let defaultMetric = Order1 let defaultMetric = Order1
graph' <- computeGraph cId Spinglass (withMetric defaultMetric) NgramsTerms repo let defaultPartitionMethod = Spinglass
graph' <- computeGraph cId defaultPartitionMethod (withMetric defaultMetric) NgramsTerms repo
mt <- defaultGraphMetadata cId "Title" repo defaultMetric mt <- defaultGraphMetadata cId "Title" repo defaultMetric
let let
graph'' = set graph_metadata (Just mt) graph' graph'' = set graph_metadata (Just mt) graph'
......
...@@ -26,24 +26,24 @@ one 8, e54847. ...@@ -26,24 +26,24 @@ one 8, e54847.
module Gargantext.Core.Viz.Phylo where module Gargantext.Core.Viz.Phylo where
import Data.Swagger
import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Control.DeepSeq (NFData) import Control.DeepSeq (NFData)
import Control.Lens (makeLenses) import Control.Lens (makeLenses)
import Data.Aeson import Data.Aeson
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Map (Map) import Data.Map (Map)
import Data.Swagger
import Data.Text (Text, pack) import Data.Text (Text, pack)
import Data.Vector (Vector) import Data.Vector (Vector)
import GHC.Generics import GHC.Generics
import GHC.IO (FilePath) import GHC.IO (FilePath)
import Gargantext.Core.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Text.Lazy as TextLazy import qualified Data.Text.Lazy as TextLazy
---------------- ----------------
-- | Config | -- -- | PhyloConfig | --
---------------- ----------------
data CorpusParser = data CorpusParser =
...@@ -180,9 +180,8 @@ instance ToSchema Quality where ...@@ -180,9 +180,8 @@ instance ToSchema Quality where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_qua_") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_qua_")
data PhyloConfig =
data Config = PhyloConfig { corpusPath :: FilePath
Config { corpusPath :: FilePath
, listPath :: FilePath , listPath :: FilePath
, outputPath :: FilePath , outputPath :: FilePath
, corpusParser :: CorpusParser , corpusParser :: CorpusParser
...@@ -201,12 +200,32 @@ data Config = ...@@ -201,12 +200,32 @@ data Config =
, exportFilter :: [Filter] , exportFilter :: [Filter]
} deriving (Show,Generic,Eq) } deriving (Show,Generic,Eq)
instance ToSchema Config
------------------------------------------------------------------------
data PhyloSubConfig =
PhyloSubConfig { _sc_phyloProximity :: Proximity
, _sc_phyloSynchrony :: Synchrony
, _sc_phyloQuality :: Quality
, _sc_timeUnit :: TimeUnit
, _sc_clique :: Clique
, _sc_exportFilter :: [Filter]
}
deriving (Show,Generic,Eq)
subConfig2config :: PhyloSubConfig -> PhyloConfig
subConfig2config subConfig = defaultConfig { phyloProximity = _sc_phyloProximity subConfig
, phyloSynchrony = _sc_phyloSynchrony subConfig
, phyloQuality = _sc_phyloQuality subConfig
, timeUnit = _sc_timeUnit subConfig
, clique = _sc_clique subConfig
, exportFilter = _sc_exportFilter subConfig
}
defaultConfig :: Config ------------------------------------------------------------------------
defaultConfig :: PhyloConfig
defaultConfig = defaultConfig =
Config { corpusPath = "corpus.csv" -- useful for commandline only PhyloConfig { corpusPath = "corpus.csv" -- useful for commandline only
, listPath = "list.csv" -- useful for commandline only , listPath = "list.csv" -- useful for commandline only
, outputPath = "data/" , outputPath = "data/"
, corpusParser = Csv 100000 , corpusParser = Csv 100000
...@@ -225,8 +244,15 @@ defaultConfig = ...@@ -225,8 +244,15 @@ defaultConfig =
, exportFilter = [ByBranchSize 3] , exportFilter = [ByBranchSize 3]
} }
instance FromJSON Config -- Main Instances
instance ToJSON Config instance ToSchema PhyloConfig
instance ToSchema PhyloSubConfig
instance FromJSON PhyloConfig
instance ToJSON PhyloConfig
instance FromJSON PhyloSubConfig
instance ToJSON PhyloSubConfig
instance FromJSON CorpusParser instance FromJSON CorpusParser
instance ToJSON CorpusParser instance ToJSON CorpusParser
...@@ -298,7 +324,7 @@ defaultSoftware = ...@@ -298,7 +324,7 @@ defaultSoftware =
data PhyloParam = data PhyloParam =
PhyloParam { _phyloParam_version :: Text PhyloParam { _phyloParam_version :: Text
, _phyloParam_software :: Software , _phyloParam_software :: Software
, _phyloParam_config :: Config , _phyloParam_config :: PhyloConfig
} deriving (Generic, Show, Eq) } deriving (Generic, Show, Eq)
instance ToSchema PhyloParam where instance ToSchema PhyloParam where
...@@ -564,7 +590,8 @@ instance ToSchema PhyloExport where ...@@ -564,7 +590,8 @@ instance ToSchema PhyloExport where
-- | Lenses | -- -- | Lenses | --
---------------- ----------------
makeLenses ''Config makeLenses ''PhyloConfig
makeLenses ''PhyloSubConfig
makeLenses ''Proximity makeLenses ''Proximity
makeLenses ''SeaElevation makeLenses ''SeaElevation
makeLenses ''Quality makeLenses ''Quality
......
...@@ -17,10 +17,6 @@ Portability : POSIX ...@@ -17,10 +17,6 @@ Portability : POSIX
module Gargantext.Core.Viz.Phylo.API module Gargantext.Core.Viz.Phylo.API
where where
-- import Control.Lens ((^.))
-- import Gargantext.Core.Viz.Phylo.Example
-- import Gargantext.Database.Schema.Node (node_hyperdata)
--import Control.Monad.Reader (ask)
import Data.Aeson import Data.Aeson
import Data.Either import Data.Either
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
......
...@@ -29,7 +29,7 @@ import Gargantext.API.Prelude (GargNoServer) ...@@ -29,7 +29,7 @@ import Gargantext.API.Prelude (GargNoServer)
import Gargantext.Core.Text.Context (TermList) import Gargantext.Core.Text.Context (TermList)
import Gargantext.Core.Types (Context) import Gargantext.Core.Types (Context)
import Gargantext.Core.Types.Main (ListType(MapTerm)) import Gargantext.Core.Types.Main (ListType(MapTerm))
import Gargantext.Core.Viz.Phylo (TimeUnit(..), Date, Document(..), Config(..), Phylo) import Gargantext.Core.Viz.Phylo (TimeUnit(..), Date, Document(..), PhyloConfig(..), Phylo)
import Gargantext.Core.Viz.Phylo.PhyloExport (toPhyloExport, dotToFile) import Gargantext.Core.Viz.Phylo.PhyloExport (toPhyloExport, dotToFile)
import Gargantext.Core.Viz.Phylo.PhyloMaker (toPhylo, toPhyloStep) import Gargantext.Core.Viz.Phylo.PhyloMaker (toPhylo, toPhyloStep)
import Gargantext.Core.Viz.Phylo.PhyloTools ({-printIOMsg, printIOComment,-} setConfig) import Gargantext.Core.Viz.Phylo.PhyloTools ({-printIOMsg, printIOComment,-} setConfig)
...@@ -85,7 +85,7 @@ phylo2dot2json phylo = do ...@@ -85,7 +85,7 @@ phylo2dot2json phylo = do
flowPhyloAPI :: Config -> CorpusId -> GargNoServer Phylo flowPhyloAPI :: PhyloConfig -> CorpusId -> GargNoServer Phylo
flowPhyloAPI config cId = do flowPhyloAPI config cId = do
(mapList, corpus) <- corpusIdtoDocuments (timeUnit config) cId (mapList, corpus) <- corpusIdtoDocuments (timeUnit config) cId
phyloWithCliques <- pure $ toPhyloStep corpus mapList config phyloWithCliques <- pure $ toPhyloStep corpus mapList config
......
...@@ -96,7 +96,7 @@ nbDocsByYear :: Map Date Double ...@@ -96,7 +96,7 @@ nbDocsByYear :: Map Date Double
nbDocsByYear = docsToTimeScaleNb docs nbDocsByYear = docsToTimeScaleNb docs
config :: Config config :: PhyloConfig
config = config =
defaultConfig { phyloName = "Cesar et Cleopatre" defaultConfig { phyloName = "Cesar et Cleopatre"
, phyloLevel = 2 , phyloLevel = 2
......
...@@ -45,7 +45,7 @@ data Phylo' = PhyloBase { _phylo'_phyloBase :: Phylo} ...@@ -45,7 +45,7 @@ data Phylo' = PhyloBase { _phylo'_phyloBase :: Phylo}
| PhyloN { _phylo'_phylo1 :: Phylo} | PhyloN { _phylo'_phylo1 :: Phylo}
toPhylo' :: Phylo' -> [Document] -> TermList -> Config -> Phylo toPhylo' :: Phylo' -> [Document] -> TermList -> PhyloConfig -> Phylo
toPhylo' (PhyloN phylo) = toPhylo' toPhylo' (PhyloN phylo) = toPhylo'
toPhylo' (PhyloBase phylo) = toPhylo toPhylo' (PhyloBase phylo) = toPhylo
-} -}
...@@ -160,7 +160,7 @@ indexDates' m = map (\docs -> ...@@ -160,7 +160,7 @@ indexDates' m = map (\docs ->
-- To build the first phylo step from docs and terms -- To build the first phylo step from docs and terms
-- QL: backend entre phyloBase et phyloClique -- QL: backend entre phyloBase et phyloClique
toPhyloStep :: [Document] -> TermList -> Config -> Phylo toPhyloStep :: [Document] -> TermList -> PhyloConfig -> Phylo
toPhyloStep docs lst conf = case (getSeaElevation phyloBase) of toPhyloStep docs lst conf = case (getSeaElevation phyloBase) of
Constante _ _ -> appendGroups cliqueToGroup 1 phyloClique (updatePeriods (indexDates' docs') phyloBase) Constante _ _ -> appendGroups cliqueToGroup 1 phyloClique (updatePeriods (indexDates' docs') phyloBase)
Adaptative _ -> toGroupsProxi 1 Adaptative _ -> toGroupsProxi 1
...@@ -362,7 +362,7 @@ initPhyloLevels lvlMax pId = ...@@ -362,7 +362,7 @@ initPhyloLevels lvlMax pId =
-- To init the basic elements of a Phylo -- To init the basic elements of a Phylo
toPhyloBase :: [Document] -> TermList -> Config -> Phylo toPhyloBase :: [Document] -> TermList -> PhyloConfig -> Phylo
toPhyloBase docs lst conf = toPhyloBase docs lst conf =
let foundations = PhyloFoundations (Vector.fromList $ nub $ concat $ map text docs) lst let foundations = PhyloFoundations (Vector.fromList $ nub $ concat $ map text docs) lst
docsSources = PhyloSources (Vector.fromList $ nub $ concat $ map sources docs) docsSources = PhyloSources (Vector.fromList $ nub $ concat $ map sources docs)
......
...@@ -400,11 +400,11 @@ getSeaElevation :: Phylo -> SeaElevation ...@@ -400,11 +400,11 @@ getSeaElevation :: Phylo -> SeaElevation
getSeaElevation phylo = seaElevation (getConfig phylo) getSeaElevation phylo = seaElevation (getConfig phylo)
getConfig :: Phylo -> Config getConfig :: Phylo -> PhyloConfig
getConfig phylo = (phylo ^. phylo_param) ^. phyloParam_config getConfig phylo = (phylo ^. phylo_param) ^. phyloParam_config
setConfig :: Config -> Phylo -> Phylo setConfig :: PhyloConfig -> Phylo -> Phylo
setConfig config phylo = phylo setConfig config phylo = phylo
& phylo_param .~ (PhyloParam & phylo_param .~ (PhyloParam
((phylo ^. phylo_param) ^. phyloParam_version) ((phylo ^. phylo_param) ^. phyloParam_version)
......
...@@ -27,7 +27,7 @@ import Gargantext.Database.Query.Tree.Root (getRootId) ...@@ -27,7 +27,7 @@ import Gargantext.Database.Query.Tree.Root (getRootId)
import Gargantext.Database.Schema.Node import Gargantext.Database.Schema.Node
import Gargantext.Prelude import Gargantext.Prelude
-- | TODO move in Config of Gargantext -- | TODO move in PhyloConfig of Gargantext
publicNodeTypes :: [NodeType] publicNodeTypes :: [NodeType]
publicNodeTypes = [NodeDashboard, NodeGraph, NodePhylo, NodeFile] publicNodeTypes = [NodeDashboard, NodeGraph, NodePhylo, NodeFile]
......
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