[config] more config refactoring

parent f40638e7
Pipeline #6583 failed with stages
...@@ -54,18 +54,9 @@ ini_p = fmap CCMD_ini $ IniArgs ...@@ -54,18 +54,9 @@ ini_p = fmap CCMD_ini $ IniArgs
convertConfigs :: Ini.GargConfig -> IniMail.MailConfig -> IniNLP.NLPConfig -> PGS.ConnectInfo -> Config.GargConfig convertConfigs :: Ini.GargConfig -> IniMail.MailConfig -> IniNLP.NLPConfig -> PGS.ConnectInfo -> Config.GargConfig
convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo = convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo =
Config.GargConfig { _gc_backend_name Config.GargConfig { _gc_secrets = CTypes.SecretsConfig { _s_master_user = _gc_masteruser
, _gc_url , _s_secret_key = _gc_secretkey }
, _gc_url_backend_api
, _gc_masteruser
, _gc_secretkey
, _gc_datafilepath , _gc_datafilepath
, _gc_max_docs_parsers
, _gc_max_docs_scrapers
, _gc_js_job_timeout
, _gc_js_id_timeout
, _gc_pubmed_api_key
, _gc_epo_api_url
, _gc_mail_config = iniMail , _gc_mail_config = iniMail
, _gc_nlp_config = nlpConfig , _gc_nlp_config = nlpConfig
, _gc_frontend_config = mkFrontendConfig ini , _gc_frontend_config = mkFrontendConfig ini
...@@ -75,7 +66,15 @@ convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo = ...@@ -75,7 +66,15 @@ convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo =
, _f_calc_url = _gc_frame_calc_url , _f_calc_url = _gc_frame_calc_url
, _f_visio_url = _gc_frame_visio_url , _f_visio_url = _gc_frame_visio_url
, _f_searx_url = _gc_frame_searx_url , _f_searx_url = _gc_frame_searx_url
, _f_istex_url = _gc_frame_istex_url } } , _f_istex_url = _gc_frame_istex_url }
, _gc_jobs = CTypes.JobsConfig { _jc_max_docs_parsers = _gc_max_docs_parsers
, _jc_max_docs_scrapers = _gc_max_docs_scrapers
, _jc_js_job_timeout = _gc_js_job_timeout
, _jc_js_id_timeout = _gc_js_id_timeout }
, _gc_apis = CTypes.APIsConfig { _ac_pubmed_api_key = _gc_pubmed_api_key
, _ac_epo_api_url = _gc_epo_api_url }
}
mkFrontendConfig :: Ini.GargConfig -> CTypes.FrontendConfig mkFrontendConfig :: Ini.GargConfig -> CTypes.FrontendConfig
mkFrontendConfig (Ini.GargConfig { .. }) = mkFrontendConfig (Ini.GargConfig { .. }) =
......
...@@ -23,6 +23,7 @@ import Gargantext.API.Dev (withDevEnv, runCmdDev) ...@@ -23,6 +23,7 @@ import Gargantext.API.Dev (withDevEnv, runCmdDev)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types
import Gargantext.API.Node () -- instances only import Gargantext.API.Node () -- instances only
import Gargantext.Core.Config (GargConfig(..)) import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Core.Config.Types (SecretsConfig(..))
import Gargantext.Core.Config.Utils (readConfig) import Gargantext.Core.Config.Utils (readConfig)
import Gargantext.Core.Types.Individu (User(..), arbitraryNewUsers, NewUser(..), arbitraryUsername, GargPassword(..)) import Gargantext.Core.Types.Individu (User(..), arbitraryNewUsers, NewUser(..), arbitraryUsername, GargPassword(..))
import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMkRootWithCorpus) import Gargantext.Database.Action.Flow (getOrMkRoot, getOrMkRootWithCorpus)
...@@ -47,7 +48,7 @@ initCLI (InitArgs settingsPath) = do ...@@ -47,7 +48,7 @@ initCLI (InitArgs settingsPath) = do
email <- getLine email <- getLine
cfg <- readConfig settingsPath cfg <- readConfig settingsPath
let secret = _gc_secretkey cfg let secret = _s_secret_key $ _gc_secrets cfg
let createUsers :: forall env. HasSettings env => DBCmd' env BackendInternalError Int64 let createUsers :: forall env. HasSettings env => DBCmd' env BackendInternalError Int64
createUsers = insertNewUsers (NewUser "gargantua" (cs email) (GargPassword $ cs password) createUsers = insertNewUsers (NewUser "gargantua" (cs email) (GargPassword $ cs password)
......
...@@ -22,6 +22,7 @@ import Data.List qualified as List (cycle, concat, take, unlines) ...@@ -22,6 +22,7 @@ import Data.List qualified as List (cycle, concat, take, unlines)
import Gargantext.API.Dev (withDevEnv) import Gargantext.API.Dev (withDevEnv)
import Gargantext.API.Node () -- instances only import Gargantext.API.Node () -- instances only
import Gargantext.Core.Config (GargConfig(..)) import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Core.Config.Types (SecretsConfig(..))
import Gargantext.Core.Config.Utils (readConfig) import Gargantext.Core.Config.Utils (readConfig)
import Gargantext.Prelude import Gargantext.Prelude
import Options.Applicative import Options.Applicative
...@@ -48,7 +49,7 @@ upgradeCLI (UpgradeArgs settingsFile) = do ...@@ -48,7 +49,7 @@ upgradeCLI (UpgradeArgs settingsFile) = do
_ok <- getLine _ok <- getLine
cfg <- readConfig settingsFile cfg <- readConfig settingsFile
let _secret = _gc_secretkey cfg let _secret = _s_secret_key $ _gc_secrets cfg
withDevEnv settingsFile $ \_env -> do withDevEnv settingsFile $ \_env -> do
-- _ <- runCmdDev env addIndex -- _ <- runCmdDev env addIndex
......
...@@ -32,8 +32,8 @@ import Gargantext.API.Errors.Types ...@@ -32,8 +32,8 @@ import Gargantext.API.Errors.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.AsyncUpdates.CentralExchange qualified as CE import Gargantext.Core.AsyncUpdates.CentralExchange qualified as CE
import Gargantext.Core.AsyncUpdates.Dispatcher qualified as D import Gargantext.Core.AsyncUpdates.Dispatcher qualified as D
import Gargantext.Core.Config (GargConfig(..), gc_js_job_timeout, gc_js_id_timeout) import Gargantext.Core.Config (GargConfig(..), gc_jobs)
import Gargantext.Core.Config.Types (SettingsFile(..), _fc_cors, _fc_microservices) import Gargantext.Core.Config.Types (SettingsFile(..), _fc_cors, _fc_microservices, jc_js_job_timeout, jc_js_id_timeout)
import Gargantext.Core.Config.Utils (readConfig) import Gargantext.Core.Config.Utils (readConfig)
import Gargantext.Core.NLP (nlpServerMap) import Gargantext.Core.NLP (nlpServerMap)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
...@@ -203,8 +203,8 @@ newEnv logger port settingsFile@(SettingsFile sf) = do ...@@ -203,8 +203,8 @@ newEnv logger port settingsFile@(SettingsFile sf) = do
secret <- Jobs.genSecret secret <- Jobs.genSecret
let jobs_settings = (Jobs.defaultJobSettings 1 secret) let jobs_settings = (Jobs.defaultJobSettings 1 secret)
& Jobs.l_jsJobTimeout .~ (fromIntegral $ config_env ^. hasConfig ^. gc_js_job_timeout) & Jobs.l_jsJobTimeout .~ (fromIntegral $ config_env ^. hasConfig ^. gc_jobs . jc_js_job_timeout)
& Jobs.l_jsIDTimeout .~ (fromIntegral $ config_env ^. hasConfig ^. gc_js_id_timeout) & Jobs.l_jsIDTimeout .~ (fromIntegral $ config_env ^. hasConfig ^. gc_jobs . jc_js_id_timeout)
!jobs_env <- Jobs.newJobEnv jobs_settings prios' manager_env !jobs_env <- Jobs.newJobEnv jobs_settings prios' manager_env
!central_exchange <- forkIO $ CE.gServer (_gc_notifications_config config_env) !central_exchange <- forkIO $ CE.gServer (_gc_notifications_config config_env)
......
...@@ -33,6 +33,7 @@ import Gargantext.Database.Query.Table.Node.Error ...@@ -33,6 +33,7 @@ import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Tree import Gargantext.Database.Query.Tree
import Gargantext.Database.Query.Tree.Root import Gargantext.Database.Query.Tree.Root
import Gargantext.Core.Config (GargConfig(..)) import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Core.Config.Types (SecretsConfig(..))
import Prelude import Prelude
import Servant import Servant
import Servant.API.Routes import Servant.API.Routes
...@@ -139,7 +140,7 @@ check (AuthenticatedUser loggedUserNodeId loggedUserUserId) = \case ...@@ -139,7 +140,7 @@ check (AuthenticatedUser loggedUserNodeId loggedUserUserId) = \case
-> enforce err403 $ (loggedUserUserId == requestedUserId) -> enforce err403 $ (loggedUserUserId == requestedUserId)
AC_master_user _requestedNodeId AC_master_user _requestedNodeId
-> do -> do
masterUsername <- _gc_masteruser <$> view hasConfig masterUsername <- _s_master_user . _gc_secrets <$> view hasConfig
masterNodeId <- getRootId (UserName masterUsername) masterNodeId <- getRootId (UserName masterUsername)
enforce err403 $ masterNodeId == loggedUserNodeId enforce err403 $ masterNodeId == loggedUserNodeId
AC_node_descendant nodeId AC_node_descendant nodeId
......
...@@ -28,6 +28,7 @@ import Data.Swagger ( ToSchema(..) ) ...@@ -28,6 +28,7 @@ import Data.Swagger ( ToSchema(..) )
import Data.Text qualified as T import Data.Text qualified as T
import Data.Text.Encoding qualified as TE import Data.Text.Encoding qualified as TE
import EPO.API.Client.Types qualified as EPO import EPO.API.Client.Types qualified as EPO
import Gargantext.API.Admin.Orchestrator.Types qualified as API
import Gargantext.API.Admin.Types (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Ngrams (commitStatePatch, Versioned(..)) import Gargantext.API.Ngrams (commitStatePatch, Versioned(..))
import Gargantext.API.Node.Corpus.New.Types ( FileFormat(..), FileType(..) ) import Gargantext.API.Node.Corpus.New.Types ( FileFormat(..), FileType(..) )
...@@ -36,10 +37,11 @@ import Gargantext.API.Node.Corpus.Types ( Datafield(Web), database2origin ) ...@@ -36,10 +37,11 @@ import Gargantext.API.Node.Corpus.Types ( Datafield(Web), database2origin )
import Gargantext.API.Node.Corpus.Update (addLanguageToCorpus) import Gargantext.API.Node.Corpus.Update (addLanguageToCorpus)
import Gargantext.API.Node.Types import Gargantext.API.Node.Types
import Gargantext.Core (withDefaultLanguage, defaultLanguage) import Gargantext.Core (withDefaultLanguage, defaultLanguage)
import Gargantext.Core.Config (gc_jobs)
import Gargantext.Core.Config.Types (jc_max_docs_parsers)
import Gargantext.Core.NodeStory (HasNodeStoryImmediateSaver, HasNodeArchiveStoryImmediateSaver, currentVersion, NgramsStatePatch') import Gargantext.Core.NodeStory (HasNodeStoryImmediateSaver, HasNodeArchiveStoryImmediateSaver, currentVersion, NgramsStatePatch')
import Gargantext.API.Admin.Orchestrator.Types qualified as API
import Gargantext.Core.Text.Corpus.Query qualified as API
import Gargantext.Core.Text.Corpus.Parsers qualified as Parser (FileType(..), parseFormatC, _ParseFormatError) import Gargantext.Core.Text.Corpus.Parsers qualified as Parser (FileType(..), parseFormatC, _ParseFormatError)
import Gargantext.Core.Text.Corpus.Query qualified as API
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Action.Flow (flowCorpus, getDataText, flowDataText, TermType(..){-, allDataOrigins-}) import Gargantext.Database.Action.Flow (flowCorpus, getDataText, flowDataText, TermType(..){-, allDataOrigins-})
...@@ -57,7 +59,6 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) ...@@ -57,7 +59,6 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Query.Tree.Root (MkCorpusUser(MkCorpusUserNormalCorpusIds)) import Gargantext.Database.Query.Tree.Root (MkCorpusUser(MkCorpusUserNormalCorpusIds))
import Gargantext.Database.Schema.Node (node_hyperdata) import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Config (gc_max_docs_parsers)
import Gargantext.System.Logging ( logLocM, LogLevel(..) ) import Gargantext.System.Logging ( logLocM, LogLevel(..) )
import Gargantext.Utils.Jobs.Monad (JobHandle, MonadJobStatus(..)) import Gargantext.Utils.Jobs.Monad (JobHandle, MonadJobStatus(..))
...@@ -237,7 +238,7 @@ addToCorpusWithForm user cid nwf jobHandle = do ...@@ -237,7 +238,7 @@ addToCorpusWithForm user cid nwf jobHandle = do
let l = nwf ^. wf_lang . non defaultLanguage let l = nwf ^. wf_lang . non defaultLanguage
addLanguageToCorpus cid l addLanguageToCorpus cid l
limit' <- view $ hasConfig . gc_max_docs_parsers limit' <- view $ hasConfig . gc_jobs . jc_max_docs_parsers
let limit = fromIntegral limit' :: Integer let limit = fromIntegral limit' :: Integer
let let
parseC = case (nwf ^. wf_filetype) of parseC = case (nwf ^. wf_filetype) of
......
...@@ -10,7 +10,8 @@ import Data.Validity qualified as V ...@@ -10,7 +10,8 @@ import Data.Validity qualified as V
import Gargantext.API.Admin.Types (appPort, settings, Settings) import Gargantext.API.Admin.Types (appPort, settings, Settings)
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Routes.Named.Share qualified as Named import Gargantext.API.Routes.Named.Share qualified as Named
import Gargantext.Core.Config (gc_url, GargConfig) import Gargantext.Core.Config (GargConfig, gc_frontend_config)
import Gargantext.Core.Config.Types (fc_url)
import Gargantext.Core.Types (NodeType, NodeId, unNodeId, _ValidationError) import Gargantext.Core.Types (NodeType, NodeId, unNodeId, _ValidationError)
import Gargantext.Database.Prelude (HasConfig (hasConfig), CmdCommon) import Gargantext.Database.Prelude (HasConfig (hasConfig), CmdCommon)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -39,7 +40,7 @@ get_url :: Maybe NodeType ...@@ -39,7 +40,7 @@ get_url :: Maybe NodeType
-> Settings -> Settings
-> Either String Named.ShareLink -> Either String Named.ShareLink
get_url nt id gc stgs = do get_url nt id gc stgs = do
let urlHost = T.unpack $ gc ^. gc_url let urlHost = T.unpack $ gc ^. gc_frontend_config . fc_url
let urlPort = stgs ^. appPort let urlPort = stgs ^. appPort
t <- maybe (Left "Invalid node Type") Right nt t <- maybe (Left "Invalid node Type") Right nt
i <- maybe (Left "Invalid node ID") Right id i <- maybe (Left "Invalid node ID") Right id
......
...@@ -31,10 +31,11 @@ import Gargantext.API.Node.Corpus.New qualified as New ...@@ -31,10 +31,11 @@ import Gargantext.API.Node.Corpus.New qualified as New
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Routes.Named.Annuaire qualified as Named import Gargantext.API.Routes.Named.Annuaire qualified as Named
import Gargantext.API.Routes.Named.Corpus qualified as Named import Gargantext.API.Routes.Named.Corpus qualified as Named
import Gargantext.Core.Config (gc_jobs)
import Gargantext.Core.Config.Types (jc_max_docs_scrapers)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Prelude (HasConfig(..)) import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Config (gc_max_docs_scrapers)
import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..)) import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Servant import Servant
import Servant.Auth.Swagger () import Servant.Auth.Swagger ()
...@@ -55,7 +56,7 @@ waitAPI n = do ...@@ -55,7 +56,7 @@ waitAPI n = do
addCorpusWithQuery :: User -> Named.AddWithQuery (AsServerT (GargM Env BackendInternalError)) addCorpusWithQuery :: User -> Named.AddWithQuery (AsServerT (GargM Env BackendInternalError))
addCorpusWithQuery user = Named.AddWithQuery $ \cid -> AsyncJobs $ addCorpusWithQuery user = Named.AddWithQuery $ \cid -> AsyncJobs $
serveJobsAPI AddCorpusQueryJob $ \jHandle q -> do serveJobsAPI AddCorpusQueryJob $ \jHandle q -> do
limit <- view $ hasConfig . gc_max_docs_scrapers limit <- view $ hasConfig . gc_jobs . jc_max_docs_scrapers
New.addToCorpusWithQuery user cid q (Just $ fromIntegral limit) jHandle New.addToCorpusWithQuery user cid q (Just $ fromIntegral limit) jHandle
{- let log' x = do {- let log' x = do
printDebug "addToCorpusWithQuery" x printDebug "addToCorpusWithQuery" x
......
...@@ -18,14 +18,15 @@ import Gargantext.API.Auth.PolicyCheck () ...@@ -18,14 +18,15 @@ import Gargantext.API.Auth.PolicyCheck ()
import Gargantext.API.Errors import Gargantext.API.Errors
import Gargantext.API.GraphQL as GraphQL import Gargantext.API.GraphQL as GraphQL
import Gargantext.API.Prelude (GargM) import Gargantext.API.Prelude (GargM)
import Gargantext.API.Server.Named.Public (serverPublicGargAPI)
import Gargantext.API.Routes.Named import Gargantext.API.Routes.Named
import Gargantext.API.Server.Named.Public (serverPublicGargAPI)
import Gargantext.API.Swagger (swaggerDoc) import Gargantext.API.Swagger (swaggerDoc)
import Gargantext.API.ThrowAll (serverPrivateGargAPI) import Gargantext.API.ThrowAll (serverPrivateGargAPI)
import Gargantext.Core.AsyncUpdates.Dispatcher.WebSocket qualified as Dispatcher import Gargantext.Core.AsyncUpdates.Dispatcher.WebSocket qualified as Dispatcher
import Gargantext.Core.Config (gc_frontend_config)
import Gargantext.Core.Config.Types (fc_url_backend_api)
import Gargantext.Database.Prelude (hasConfig) import Gargantext.Database.Prelude (hasConfig)
import Gargantext.Prelude hiding (Handler, catch) import Gargantext.Prelude hiding (Handler, catch)
import Gargantext.Core.Config (gc_url_backend_api)
import Gargantext.System.Logging (logLocM, LogLevel(..)) import Gargantext.System.Logging (logLocM, LogLevel(..))
import Paths_gargantext qualified as PG -- cabal magic build module import Paths_gargantext qualified as PG -- cabal magic build module
import Servant import Servant
...@@ -40,7 +41,7 @@ serverGargAPI env ...@@ -40,7 +41,7 @@ serverGargAPI env
, gargForgotPasswordAsyncAPI = forgotPasswordAsync , gargForgotPasswordAsyncAPI = forgotPasswordAsync
, gargVersionAPI = gargVersion , gargVersionAPI = gargVersion
, gargPrivateAPI = serverPrivateGargAPI , gargPrivateAPI = serverPrivateGargAPI
, gargPublicAPI = serverPublicGargAPI (env ^. hasConfig . gc_url_backend_api) , gargPublicAPI = serverPublicGargAPI (env ^. hasConfig . gc_frontend_config . fc_url_backend_api)
} }
where where
gargVersion :: GargVersion (AsServerT (GargM Env BackendInternalError)) gargVersion :: GargVersion (AsServerT (GargM Env BackendInternalError))
......
...@@ -18,24 +18,16 @@ module Gargantext.Core.Config ( ...@@ -18,24 +18,16 @@ module Gargantext.Core.Config (
GargConfig(..) GargConfig(..)
-- * Lenses -- * Lenses
, gc_backend_name
, gc_datafilepath , gc_datafilepath
, gc_epo_api_url
, gc_js_id_timeout
, gc_js_job_timeout
, gc_masteruser
, gc_max_docs_parsers
, gc_max_docs_scrapers
, gc_pubmed_api_key
, gc_secretkey
, gc_url
, gc_url_backend_api
, gc_frontend_config , gc_frontend_config
, gc_mail_config , gc_mail_config
, gc_database_config , gc_database_config
, gc_nlp_config , gc_nlp_config
, gc_notifications_config , gc_notifications_config
, gc_frames , gc_frames
, gc_jobs
, gc_secrets
, gc_apis
, mkProxyUrl , mkProxyUrl
) where ) where
...@@ -54,32 +46,18 @@ import Toml.Schema ...@@ -54,32 +46,18 @@ import Toml.Schema
-- stripRight :: Char -> T.Text -> T.Text -- stripRight :: Char -> T.Text -> T.Text
-- stripRight c s = if T.last s == c then stripRight c (T.take (T.length s - 1) s) else s -- stripRight c s = if T.last s == c then stripRight c (T.take (T.length s - 1) s) else s
data GargConfig = GargConfig { _gc_backend_name :: !T.Text data GargConfig = GargConfig { _gc_datafilepath :: !FilePath
, _gc_url :: !T.Text
, _gc_url_backend_api :: !T.Text
, _gc_masteruser :: !T.Text
, _gc_secretkey :: !T.Text
, _gc_datafilepath :: !FilePath
-- , _gc_repofilepath :: !FilePath -- , _gc_repofilepath :: !FilePath
, _gc_max_docs_parsers :: !Integer
, _gc_max_docs_scrapers :: !Integer
, _gc_js_job_timeout :: !Integer
, _gc_js_id_timeout :: !Integer
, _gc_pubmed_api_key :: !T.Text
, _gc_epo_api_url :: !T.Text
, _gc_frontend_config :: !FrontendConfig , _gc_frontend_config :: !FrontendConfig
, _gc_mail_config :: !MailConfig , _gc_mail_config :: !MailConfig
, _gc_database_config :: !PSQL.ConnectInfo , _gc_database_config :: !PSQL.ConnectInfo
, _gc_nlp_config :: !NLPConfig , _gc_nlp_config :: !NLPConfig
, _gc_notifications_config :: !NotificationsConfig , _gc_notifications_config :: !NotificationsConfig
, _gc_frames :: !FramesConfig , _gc_frames :: !FramesConfig
, _gc_jobs :: !JobsConfig
, _gc_secrets :: !SecretsConfig
, _gc_apis :: !APIsConfig
} }
deriving (Generic, Show) deriving (Generic, Show)
...@@ -87,62 +65,45 @@ makeLenses ''GargConfig ...@@ -87,62 +65,45 @@ makeLenses ''GargConfig
instance FromValue GargConfig where instance FromValue GargConfig where
fromValue = parseTableFromValue $ do fromValue = parseTableFromValue $ do
_gc_frontend_config@(FrontendConfig { .. }) <- reqKey "frontend" _gc_frontend_config <- reqKey "frontend"
_gc_mail_config <- reqKey "mail" _gc_mail_config <- reqKey "mail"
db_config <- reqKey "database" db_config <- reqKey "database"
_gc_nlp_config <- reqKey "nlp" _gc_nlp_config <- reqKey "nlp"
secrets <- reqKey "secrets" _gc_secrets <- reqKey "secrets"
_gc_datafilepath <- reqKeyOf "paths" $ parseTableFromValue $ reqKey "data_filepath" _gc_datafilepath <- reqKeyOf "paths" $ parseTableFromValue $ reqKey "data_filepath"
_gc_frames <- reqKeyOf "external" $ parseTableFromValue $ reqKey "frames" _gc_frames <- reqKeyOf "external" $ parseTableFromValue $ reqKey "frames"
jobs <- reqKey "jobs" _gc_jobs <- reqKey "jobs"
apis <- reqKey "apis" _gc_apis <- reqKey "apis"
_gc_notifications_config <- reqKey "notifications" _gc_notifications_config <- reqKey "notifications"
return $ GargConfig { _gc_backend_name = _fc_backend_name return $ GargConfig { _gc_datafilepath
, _gc_url = _fc_url , _gc_jobs
, _gc_url_backend_api = _fc_url_backend_api , _gc_apis
, _gc_masteruser = _s_master_user secrets
, _gc_secretkey = _s_secret_key secrets
, _gc_datafilepath
, _gc_max_docs_parsers = _jc_max_docs_parsers jobs
, _gc_max_docs_scrapers = _jc_max_docs_scrapers jobs
, _gc_js_job_timeout = _jc_js_job_timeout jobs
, _gc_js_id_timeout = _jc_js_id_timeout jobs
, _gc_pubmed_api_key = _ac_pubmed_api_key apis
, _gc_epo_api_url = _ac_epo_api_url apis
, _gc_frontend_config , _gc_frontend_config
, _gc_mail_config , _gc_mail_config
, _gc_database_config = unTOMLConnectInfo db_config , _gc_database_config = unTOMLConnectInfo db_config
, _gc_nlp_config , _gc_nlp_config
, _gc_notifications_config , _gc_notifications_config
, _gc_frames } , _gc_frames
, _gc_secrets }
instance ToValue GargConfig where instance ToValue GargConfig where
toValue = defaultTableToValue toValue = defaultTableToValue
instance ToTable GargConfig where instance ToTable GargConfig where
toTable (GargConfig { .. }) = toTable (GargConfig { .. }) =
table [ "frontend" .= _gc_frontend_config table [ "frontend" .= _gc_frontend_config
, "secrets" .= secrets , "secrets" .= _gc_secrets
, "paths" .= table [ "data_filepath" .= _gc_datafilepath ] , "paths" .= table [ "data_filepath" .= _gc_datafilepath ]
, "apis" .= apis , "apis" .= _gc_apis
, "external" .= table [ "frames" .= _gc_frames ] , "external" .= table [ "frames" .= _gc_frames ]
, "jobs" .= jobs , "jobs" .= _gc_jobs
, "database" .= TOMLConnectInfo _gc_database_config , "database" .= TOMLConnectInfo _gc_database_config
, "mail" .= _gc_mail_config , "mail" .= _gc_mail_config
, "notifications" .= _gc_notifications_config , "notifications" .= _gc_notifications_config
, "nlp" .= _gc_nlp_config , "nlp" .= _gc_nlp_config
] ]
where
secrets = SecretsConfig { _s_master_user = _gc_masteruser
, _s_secret_key = _gc_secretkey }
apis = APIsConfig { _ac_pubmed_api_key = _gc_pubmed_api_key
, _ac_epo_api_url = _gc_epo_api_url }
jobs = JobsConfig { _jc_max_docs_parsers = _gc_max_docs_parsers
, _jc_max_docs_scrapers = _gc_max_docs_scrapers
, _jc_js_job_timeout = _gc_js_job_timeout
, _jc_js_id_timeout = _gc_js_id_timeout }
mkProxyUrl :: GargConfig -> MicroServicesSettings -> BaseUrl mkProxyUrl :: GargConfig -> MicroServicesSettings -> BaseUrl
mkProxyUrl GargConfig{..} MicroServicesSettings{..} = mkProxyUrl GargConfig{..} MicroServicesSettings{..} =
case parseBaseUrl (T.unpack _gc_url) of case parseBaseUrl (T.unpack $ _fc_url _gc_frontend_config) of
Nothing -> BaseUrl Http "localhost" 80 "" Nothing -> BaseUrl Http "localhost" 80 ""
Just bh -> bh { baseUrlPort = _msProxyPort } Just bh -> bh { baseUrlPort = _msProxyPort }
...@@ -14,23 +14,34 @@ TODO-SECURITY: Critical ...@@ -14,23 +14,34 @@ TODO-SECURITY: Critical
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ViewPatterns #-}
module Gargantext.Core.Config.Types module Gargantext.Core.Config.Types
( SettingsFile(..) ( APIsConfig(..)
, ac_pubmed_api_key
, ac_epo_api_url
, CORSOrigin(..) , CORSOrigin(..)
, CORSSettings(..) , CORSSettings(..)
, MicroServicesSettings(..)
, TOMLConnectInfo(..)
, FramesConfig(..) , FramesConfig(..)
, FrontendConfig(..)
, JobsConfig(..)
, APIsConfig(..)
, NotificationsConfig(..)
, SecretsConfig(..)
, f_write_url , f_write_url
, f_calc_url , f_calc_url
, f_visio_url , f_visio_url
, f_searx_url , f_searx_url
, f_istex_url , f_istex_url
, FrontendConfig(..)
, fc_url
, fc_backend_name
, fc_url_backend_api
, fc_jwt_settings
, fc_cors
, fc_microservices
, JobsConfig(..)
, jc_max_docs_parsers
, jc_max_docs_scrapers
, jc_js_job_timeout
, jc_js_id_timeout
, MicroServicesSettings(..)
, NotificationsConfig(..)
, SecretsConfig(..)
, SettingsFile(..)
, TOMLConnectInfo(..)
, corsUseOriginsForHosts , corsUseOriginsForHosts
, corsAllowedOrigins , corsAllowedOrigins
...@@ -196,6 +207,8 @@ instance ToTable FrontendConfig where ...@@ -196,6 +207,8 @@ instance ToTable FrontendConfig where
, "cors" .= _fc_cors , "cors" .= _fc_cors
, "microservices" .= _fc_microservices ] , "microservices" .= _fc_microservices ]
makeLenses ''FrontendConfig
data SecretsConfig = data SecretsConfig =
SecretsConfig { _s_master_user :: !Text SecretsConfig { _s_master_user :: !Text
...@@ -219,6 +232,7 @@ data JobsConfig = ...@@ -219,6 +232,7 @@ data JobsConfig =
, _jc_max_docs_scrapers :: !Integer , _jc_max_docs_scrapers :: !Integer
, _jc_js_job_timeout :: !Integer , _jc_js_job_timeout :: !Integer
, _jc_js_id_timeout :: !Integer } , _jc_js_id_timeout :: !Integer }
deriving (Generic, Show)
instance FromValue JobsConfig where instance FromValue JobsConfig where
fromValue = parseTableFromValue $ do fromValue = parseTableFromValue $ do
_jc_max_docs_parsers <- reqKey "max_docs_parsers" _jc_max_docs_parsers <- reqKey "max_docs_parsers"
...@@ -234,10 +248,13 @@ instance ToTable JobsConfig where ...@@ -234,10 +248,13 @@ instance ToTable JobsConfig where
, "js_job_timeout" .= _jc_js_job_timeout , "js_job_timeout" .= _jc_js_job_timeout
, "js_id_timeout" .= _jc_js_id_timeout ] , "js_id_timeout" .= _jc_js_id_timeout ]
makeLenses ''JobsConfig
data APIsConfig = data APIsConfig =
APIsConfig { _ac_pubmed_api_key :: !Text APIsConfig { _ac_pubmed_api_key :: !Text
, _ac_epo_api_url :: !Text } , _ac_epo_api_url :: !Text }
deriving (Generic, Show)
instance FromValue APIsConfig where instance FromValue APIsConfig where
fromValue = parseTableFromValue $ do fromValue = parseTableFromValue $ do
_ac_pubmed_api_key <- reqKeyOf "pubmed" $ parseTableFromValue $ reqKey "api_key" _ac_pubmed_api_key <- reqKeyOf "pubmed" $ parseTableFromValue $ reqKey "api_key"
...@@ -250,6 +267,8 @@ instance ToTable APIsConfig where ...@@ -250,6 +267,8 @@ instance ToTable APIsConfig where
, "epo" .= table [ "api_url" .= _ac_epo_api_url ] , "epo" .= table [ "api_url" .= _ac_epo_api_url ]
] ]
makeLenses ''APIsConfig
data NotificationsConfig = data NotificationsConfig =
NotificationsConfig { _nc_central_exchange_bind :: !T.Text NotificationsConfig { _nc_central_exchange_bind :: !T.Text
......
...@@ -15,12 +15,13 @@ import Control.Lens (view) ...@@ -15,12 +15,13 @@ import Control.Lens (view)
import Control.Monad.Trans.Control (MonadBaseControl) import Control.Monad.Trans.Control (MonadBaseControl)
import Data.List qualified as List import Data.List qualified as List
import Data.Text (splitOn) import Data.Text (splitOn)
import Gargantext.Core.Config (gc_frontend_config)
import Gargantext.Core.Config.Types (fc_url, fc_backend_name)
import Gargantext.Core.Config.Mail (gargMail, GargMail(..), MailConfig)
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Database.Prelude (HasConfig(..)) import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Database.Schema.User (UserLight(..)) import Gargantext.Database.Schema.User (UserLight(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Config (gc_url, gc_backend_name)
import Gargantext.Core.Config.Mail (gargMail, GargMail(..), MailConfig)
import Network.URI.Encode (encodeText) import Network.URI.Encode (encodeText)
...@@ -74,7 +75,8 @@ mail mailCfg model = do ...@@ -74,7 +75,8 @@ mail mailCfg model = do
let let
(m,u) = email_to model (m,u) = email_to model
subject = email_subject model subject = email_subject model
body = emailWith (ServerAddress (view gc_backend_name cfg) (view gc_url cfg)) model body = emailWith (ServerAddress (view (gc_frontend_config . fc_backend_name) cfg)
(view (gc_frontend_config . fc_url) cfg)) model
liftBase $ gargMail mailCfg (GargMail { gm_to = m liftBase $ gargMail mailCfg (GargMail { gm_to = m
, gm_name = Just u , gm_name = Just u
, gm_subject = subject , gm_subject = subject
......
...@@ -66,6 +66,8 @@ import EPO.API.Client.Types qualified as EPO ...@@ -66,6 +66,8 @@ import EPO.API.Client.Types qualified as EPO
import Gargantext.API.Ngrams.Tools (getTermsWith) import Gargantext.API.Ngrams.Tools (getTermsWith)
import Gargantext.Core (Lang(..), NLPServerConfig, withDefaultLanguage) import Gargantext.Core (Lang(..), NLPServerConfig, withDefaultLanguage)
import Gargantext.Core.AsyncUpdates.CentralExchange.Types (HasCentralExchangeNotification(ce_notify), CEMessage(..)) import Gargantext.Core.AsyncUpdates.CentralExchange.Types (HasCentralExchangeNotification(ce_notify), CEMessage(..))
import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Core.Config.Types (APIsConfig(..))
import Gargantext.Core.Ext.IMTUser (readFile_Annuaire) import Gargantext.Core.Ext.IMTUser (readFile_Annuaire)
import Gargantext.Core.NLP (HasNLPServer, nlpServerGet) import Gargantext.Core.NLP (HasNLPServer, nlpServerGet)
import Gargantext.Core.NodeStory.Types (HasNodeStory) import Gargantext.Core.NodeStory.Types (HasNodeStory)
...@@ -103,7 +105,6 @@ import Gargantext.Database.Query.Tree.Root (MkCorpusUser(..), getOrMkRoot, getOr ...@@ -103,7 +105,6 @@ import Gargantext.Database.Query.Tree.Root (MkCorpusUser(..), getOrMkRoot, getOr
import Gargantext.Database.Schema.Ngrams ( indexNgrams, text2ngrams ) import Gargantext.Database.Schema.Ngrams ( indexNgrams, text2ngrams )
import Gargantext.Database.Schema.Node (node_hyperdata) import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude hiding (to) import Gargantext.Prelude hiding (to)
import Gargantext.Core.Config (GargConfig(..))
import Gargantext.System.Logging ( logLocM, LogLevel(DEBUG), MonadLogger ) import Gargantext.System.Logging ( logLocM, LogLevel(DEBUG), MonadLogger )
import Gargantext.Utils.Jobs.Monad ( JobHandle, MonadJobStatus(..) ) import Gargantext.Utils.Jobs.Monad ( JobHandle, MonadJobStatus(..) )
import PUBMED.Types qualified as PUBMED import PUBMED.Types qualified as PUBMED
...@@ -138,7 +139,7 @@ getDataText :: (HasNodeError err, HasSettings env) ...@@ -138,7 +139,7 @@ getDataText :: (HasNodeError err, HasSettings env)
-> DBCmd' env err (Either API.GetCorpusError DataText) -> DBCmd' env err (Either API.GetCorpusError DataText)
getDataText (ExternalOrigin api) la q mPubmedAPIKey mAuthKey li = do getDataText (ExternalOrigin api) la q mPubmedAPIKey mAuthKey li = do
cfg <- view hasConfig cfg <- view hasConfig
eRes <- liftBase $ API.get api (_tt_lang la) q mPubmedAPIKey mAuthKey (_gc_epo_api_url cfg) li eRes <- liftBase $ API.get api (_tt_lang la) q mPubmedAPIKey mAuthKey (_ac_epo_api_url $ _gc_apis cfg) li
pure $ DataNew <$> eRes pure $ DataNew <$> eRes
getDataText (InternalOrigin _) la q _ _ _li = do getDataText (InternalOrigin _) la q _ _ _li = do
(_masterUserId, _masterRootId, cId) <- getOrMkRootWithCorpus MkCorpusUserMaster (Nothing :: Maybe HyperdataCorpus) (_masterUserId, _masterRootId, cId) <- getOrMkRootWithCorpus MkCorpusUserMaster (Nothing :: Maybe HyperdataCorpus)
......
...@@ -25,7 +25,7 @@ import Data.Text qualified as T ...@@ -25,7 +25,7 @@ import Data.Text qualified as T
import Gargantext.API.Admin.Types (settings, _microservicesSettings, HasSettings) import Gargantext.API.Admin.Types (settings, _microservicesSettings, HasSettings)
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Config (GargConfig(..), mkProxyUrl) import Gargantext.Core.Config (GargConfig(..), mkProxyUrl)
import Gargantext.Core.Config.Types (FramesConfig(..), MicroServicesSettings(..)) import Gargantext.Core.Config.Types (FramesConfig(..), MicroServicesSettings(..), SecretsConfig(..))
import Gargantext.Core.Types (Name) import Gargantext.Core.Types (Name)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Hyperdata.Default import Gargantext.Database.Admin.Types.Hyperdata.Default
...@@ -127,7 +127,7 @@ mkNodeWithParent_ConfigureHyperdata' nt (Just i) uId name = do ...@@ -127,7 +127,7 @@ mkNodeWithParent_ConfigureHyperdata' nt (Just i) uId name = do
NodeFrameVisio -> pure $ _f_visio_url $ _gc_frames cfg NodeFrameVisio -> pure $ _f_visio_url $ _gc_frames cfg
_ -> nodeError NeedsConfiguration _ -> nodeError NeedsConfiguration
let let
s = _gc_secretkey cfg s = _s_secret_key $ _gc_secrets cfg
hd = HyperdataFrame u (hash $ s <> (show nodeId)) hd = HyperdataFrame u (hash $ s <> (show nodeId))
_ <- updateHyperdata nodeId hd _ <- updateHyperdata nodeId hd
pure [nodeId] pure [nodeId]
......
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