[settings] loglevel moved to garg config

parent 0902bab3
Pipeline #6664 passed with stages
in 63 minutes and 39 seconds
...@@ -19,6 +19,7 @@ Import a corpus binary. ...@@ -19,6 +19,7 @@ Import a corpus binary.
module CLI.Ini where module CLI.Ini where
import CLI.Types import CLI.Types
import Control.Monad.Logger (LogLevel(LevelDebug))
import Data.Text qualified as T import Data.Text qualified as T
import Database.PostgreSQL.Simple qualified as PGS import Database.PostgreSQL.Simple qualified as PGS
import Gargantext.Core.Config qualified as Config import Gargantext.Core.Config qualified as Config
...@@ -73,7 +74,7 @@ convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo = ...@@ -73,7 +74,7 @@ convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo =
, _jc_js_id_timeout = _gc_js_id_timeout } , _jc_js_id_timeout = _gc_js_id_timeout }
, _gc_apis = CTypes.APIsConfig { _ac_pubmed_api_key = _gc_pubmed_api_key , _gc_apis = CTypes.APIsConfig { _ac_pubmed_api_key = _gc_pubmed_api_key
, _ac_epo_api_url = _gc_epo_api_url } , _ac_epo_api_url = _gc_epo_api_url }
, _gc_log_level = LevelDebug
} }
mkFrontendConfig :: Ini.GargConfig -> CTypes.FrontendConfig mkFrontendConfig :: Ini.GargConfig -> CTypes.FrontendConfig
......
...@@ -659,6 +659,7 @@ executable gargantext-cli ...@@ -659,6 +659,7 @@ executable gargantext-cli
, gargantext , gargantext
, gargantext-prelude , gargantext-prelude
, ini ^>= 0.4.1 , ini ^>= 0.4.1
, monad-logger ^>= 0.3.36
, optparse-applicative , optparse-applicative
, optparse-generic ^>= 1.4.7 , optparse-generic ^>= 1.4.7
, parallel ^>= 3.2.2.0 , parallel ^>= 3.2.2.0
......
...@@ -20,7 +20,6 @@ module Gargantext.API.Admin.Settings ...@@ -20,7 +20,6 @@ module Gargantext.API.Admin.Settings
import Codec.Serialise (Serialise(), serialise) import Codec.Serialise (Serialise(), serialise)
import Control.Lens import Control.Lens
import Control.Monad.Logger (LogLevel(..))
import Control.Monad.Reader import Control.Monad.Reader
import Data.ByteString.Lazy qualified as L import Data.ByteString.Lazy qualified as L
import Data.Pool (Pool) import Data.Pool (Pool)
...@@ -68,9 +67,8 @@ devSettings (JwkFile jwkFile) = do ...@@ -68,9 +67,8 @@ devSettings (JwkFile jwkFile) = do
pure $ Settings pure $ Settings
{ -- _corsSettings = _gargCorsSettings { -- _corsSettings = _gargCorsSettings
-- , _microservicesSettings = _gargMicroServicesSettings -- , _microservicesSettings = _gargMicroServicesSettings
_logLevelLimit = LevelDebug
-- , _dbServer = "localhost" -- , _dbServer = "localhost"
, _sendLoginEmails = LogEmailToConsole _sendLoginEmails = LogEmailToConsole
, _scrapydUrl = fromMaybe (panicTrace "Invalid scrapy URL") $ parseBaseUrl "http://localhost:6800" , _scrapydUrl = fromMaybe (panicTrace "Invalid scrapy URL") $ parseBaseUrl "http://localhost:6800"
, _cookieSettings = defaultCookieSettings { cookieXsrfSetting = Just xsrfCookieSetting } -- TODO-SECURITY tune , _cookieSettings = defaultCookieSettings { cookieXsrfSetting = Just xsrfCookieSetting } -- TODO-SECURITY tune
, _jwtSettings = defaultJWTSettings jwk -- TODO-SECURITY tune , _jwtSettings = defaultJWTSettings jwk -- TODO-SECURITY tune
......
{--| Support in Gargantext for CORS (Cross-origin resource sharing) --}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
module Gargantext.API.Admin.Settings.CORS where
import Prelude
import Control.Arrow
import Data.Text qualified as T
import Toml
import Control.Lens hiding (iso, (.=))
import Servant.Client.Core
import Data.Maybe (fromMaybe)
newtype CORSOrigin = CORSOrigin { _CORSOrigin :: BaseUrl }
deriving (Show, Eq)
data CORSSettings =
CORSSettings {
_corsAllowedOrigins :: [CORSOrigin]
, _corsAllowedHosts :: [CORSOrigin]
-- | If 'True', we will reuse the origin whitelist
-- as the allowed hosts as well. This allows, for example,
-- to connect from \"demo.gargantext.org\" to \"dev.sub.gargantext.org\"
-- and vice-versa.
, _corsUseOriginsForHosts :: !Bool
} deriving (Show, Eq)
corsOriginCodec :: TomlBiMap CORSOrigin AnyValue
corsOriginCodec = _Orig >>> _Text
where
_Orig :: BiMap e CORSOrigin T.Text
_Orig = iso (T.pack . showBaseUrl . _CORSOrigin)
(\(T.unpack -> u) -> CORSOrigin . fromMaybe (error $ "invalid origin: " <> u) . parseBaseUrl $ u)
corsSettingsCodec :: TomlCodec CORSSettings
corsSettingsCodec = CORSSettings
<$> Toml.arrayOf corsOriginCodec "allowed-origins" .= _corsAllowedOrigins
<*> pure mempty -- FIXME(adn) Currently we don't need to support this field.
<*> Toml.bool "use-origins-for-hosts" .= _corsUseOriginsForHosts
makeLenses ''CORSSettings
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Admin.Settings.MicroServices where
import Prelude
import Control.Lens.TH
import Data.Text qualified as T
import Gargantext.Core.Config
import Servant.Client.Core.BaseUrl
import Toml
data MicroServicesSettings =
MicroServicesSettings {
-- | The port where the microservices proxy will be listening on.
_msProxyPort :: !Int
, _msProxyEnabled :: !Bool
} deriving (Show, Eq)
microServicesSettingsCodec :: TomlCodec MicroServicesSettings
microServicesSettingsCodec = MicroServicesSettings
<$> Toml.int "port" .= _msProxyPort
<*> Toml.bool "enabled" .= _msProxyEnabled
mkProxyUrl :: GargConfig -> MicroServicesSettings -> BaseUrl
mkProxyUrl GargConfig{..} MicroServicesSettings{..} =
case parseBaseUrl (T.unpack _gc_url) of
Nothing -> BaseUrl Http "localhost" 80 ""
Just bh -> bh { baseUrlPort = _msProxyPort }
makeLenses ''MicroServicesSettings
...@@ -3,7 +3,6 @@ ...@@ -3,7 +3,6 @@
module Gargantext.API.Admin.Types where module Gargantext.API.Admin.Types where
import Control.Lens import Control.Lens
import Control.Monad.Logger (LogLevel)
import GHC.Enum import GHC.Enum
import Gargantext.Prelude import Gargantext.Prelude
import Servant.Auth.Server (JWTSettings, CookieSettings(..)) import Servant.Auth.Server (JWTSettings, CookieSettings(..))
...@@ -17,10 +16,10 @@ data SendEmailType = SendEmailViaAws ...@@ -17,10 +16,10 @@ data SendEmailType = SendEmailViaAws
deriving (Show, Read, Enum, Bounded, Generic) deriving (Show, Read, Enum, Bounded, Generic)
data Settings = Settings data Settings = Settings
{ _logLevelLimit :: !LogLevel -- log level from the monad-logger package {
-- , _dbServer :: Text -- , _dbServer :: Text
-- ^ this is not used yet -- ^ this is not used yet
, _jwtSettings :: !JWTSettings _jwtSettings :: !JWTSettings
, _cookieSettings :: !CookieSettings , _cookieSettings :: !CookieSettings
, _sendLoginEmails :: !SendEmailType , _sendLoginEmails :: !SendEmailType
, _scrapydUrl :: !BaseUrl , _scrapydUrl :: !BaseUrl
......
...@@ -28,10 +28,12 @@ module Gargantext.Core.Config ( ...@@ -28,10 +28,12 @@ module Gargantext.Core.Config (
, gc_jobs , gc_jobs
, gc_secrets , gc_secrets
, gc_apis , gc_apis
, gc_log_level
, mkProxyUrl , mkProxyUrl
) where ) where
import Control.Monad.Logger (LogLevel(LevelDebug))
import Data.Text as T import Data.Text as T
import Database.PostgreSQL.Simple qualified as PSQL import Database.PostgreSQL.Simple qualified as PSQL
import Gargantext.Core.Config.Mail (MailConfig) import Gargantext.Core.Config.Mail (MailConfig)
...@@ -59,6 +61,7 @@ data GargConfig = GargConfig { _gc_datafilepath :: ~FilePath ...@@ -59,6 +61,7 @@ data GargConfig = GargConfig { _gc_datafilepath :: ~FilePath
, _gc_jobs :: ~JobsConfig , _gc_jobs :: ~JobsConfig
, _gc_secrets :: ~SecretsConfig , _gc_secrets :: ~SecretsConfig
, _gc_apis :: ~APIsConfig , _gc_apis :: ~APIsConfig
, _gc_log_level :: ~LogLevel
} }
deriving (Generic, Show) deriving (Generic, Show)
...@@ -76,6 +79,7 @@ instance FromValue GargConfig where ...@@ -76,6 +79,7 @@ instance FromValue GargConfig where
_gc_jobs <- reqKey "jobs" _gc_jobs <- reqKey "jobs"
_gc_apis <- reqKey "apis" _gc_apis <- reqKey "apis"
_gc_notifications_config <- reqKey "notifications" _gc_notifications_config <- reqKey "notifications"
let _gc_log_level = LevelDebug
return $ GargConfig { _gc_datafilepath return $ GargConfig { _gc_datafilepath
, _gc_jobs , _gc_jobs
, _gc_apis , _gc_apis
...@@ -85,7 +89,8 @@ instance FromValue GargConfig where ...@@ -85,7 +89,8 @@ instance FromValue GargConfig where
, _gc_nlp_config , _gc_nlp_config
, _gc_notifications_config , _gc_notifications_config
, _gc_frames , _gc_frames
, _gc_secrets } , _gc_secrets
, _gc_log_level }
instance ToValue GargConfig where instance ToValue GargConfig where
toValue = defaultTableToValue toValue = defaultTableToValue
instance ToTable GargConfig where instance ToTable GargConfig where
......
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