{-| Module : Gargantext.Core.Config.NLP Description : Copyright : (c) CNRS, 2017-Present License : AGPL + CECILL v3 Maintainer : team@gargantext.org Stability : experimental Portability : POSIX -} {-# OPTIONS_GHC -fno-warn-orphans #-} -- orphan 'FromValue URI' instance {-# LANGUAGE TemplateHaskell #-} module Gargantext.Core.Config.NLP ( -- * Types NLPConfig(..) -- * Lenses , nlp_default , nlp_languages ) where import Control.Monad.Fail (fail) import Data.Map.Strict qualified as Map import Data.Text qualified as T import Gargantext.Prelude import Network.URI (URI, parseURI) import Toml import Toml.Schema instance FromValue URI where fromValue (Toml.Text' _ t) = case parseURI (T.unpack t) of Nothing -> fail ("Cannot parse URI " <> T.unpack t) Just uri -> return uri fromValue _ = fail ("Expected text for URI") instance ToValue URI where toValue v = toValue (show v :: Text) data NLPConfig = NLPConfig { _nlp_default :: URI , _nlp_languages :: Map.Map T.Text URI } deriving (Generic, Show) instance FromValue NLPConfig where fromValue v = do _nlp_default <- parseTableFromValue (reqKey "EN") v -- _nlp_languages <- fromValue <$> getTable MkTable t <- parseTableFromValue getTable v _nlp_languages <- mapM fromValue (snd <$> t) return $ NLPConfig { .. } instance ToValue NLPConfig where toValue = defaultTableToValue instance ToTable NLPConfig where toTable (NLPConfig { .. }) = table ([ k .= v | (k, v) <- Map.toList _nlp_languages ] -- output the default "EN" language as well <> [ ("EN" :: Text) .= _nlp_default ]) -- readConfig :: SettingsFile -> IO NLPConfig -- readConfig (SettingsFile fp) = do -- eRes <- Toml.decodeFileEither nlpCodec fp -- case eRes of -- Left err -> panicTrace ("Error reading TOML file (nlp): " <> show err) -- Right config -> return config -- nlpCodec :: Toml.TomlCodec NLPConfig -- nlpCodec = NLPConfig -- <$> uriToml "nlp.EN" .= _nlp_default -- <*> Toml.tableMap Toml._KeyText uriToml "nlp" .= _nlp_languages -- readConfig :: FilePath -> IO NLPConfig -- readConfig fp = do -- ini <- readIniFile' fp -- let val' = val ini iniSection -- let lang_default_text = "EN" -- Change this value by one of your choice: "All", "FR", or "EN" -- let m_nlp_default = parseURI $ cs $ val' lang_default_text -- let m_nlp_keys = filter (\k -> k `notElem` [lang_default_text]) $ fromRight [] $ Ini.keys iniSection ini -- let m_nlp_other = listToMaybeAll $ (\k -> (,) k <$> (parseURI $ cs $ val' k)) <$> m_nlp_keys -- let mRet = NLPConfig <$> m_nlp_default <*> (Map.fromList <$> m_nlp_other) -- case mRet of -- Nothing -> panicTrace $ T.concat [ "Cannot read config file: _nlp_default = " -- , T.pack $ show m_nlp_default -- , ", _nlp_other = " -- , T.pack $ show m_nlp_other ] -- Just ret -> pure ret makeLenses ''NLPConfig