[toml] more settings refactor into gargconfig

parent 9d454100
Pipeline #6671 failed with stages
in 65 minutes and 44 seconds
......@@ -85,7 +85,8 @@ mkFrontendConfig (Ini.GargConfig { .. }) =
, _fc_url_backend_api = _gc_url_backend_api
, _fc_cors
, _fc_microservices
, _fc_appPort = 3000 }
, _fc_appPort = 3000
, _fc_cookie_settings = CTypes.defaultCookieSettings }
where
_fc_cors = CTypes.CORSSettings { _corsAllowedOrigins = [
toCORSOrigin "https://demo.gargantext.org"
......
......@@ -46,13 +46,13 @@ import Data.Validity
import Gargantext.API.Admin.Auth.Types (AuthContext)
import Gargantext.API.Admin.EnvTypes (Env, Mode(..), env_config, env_jwt_settings)
import Gargantext.API.Admin.Settings (newEnv)
import Gargantext.API.Admin.Types (FireWall(..), cookieSettings, settings)
import Gargantext.API.Admin.Types (FireWall(..))
import Gargantext.API.Middleware (logStdoutDevSanitised)
import Gargantext.API.Routes.Named (API)
import Gargantext.API.Routes.Named.EKG
import Gargantext.API.Server.Named (server)
import Gargantext.Core.Config (gc_notifications_config, gc_frontend_config)
import Gargantext.Core.Config.Types (CORSOrigin(..), CORSSettings, MicroServicesProxyStatus(..), NotificationsConfig(..), PortNumber, SettingsFile(..), corsAllowedOrigins, fc_cors, microServicesProxyStatus)
import Gargantext.Core.Config.Types (CORSOrigin(..), CORSSettings, MicroServicesProxyStatus(..), NotificationsConfig(..), PortNumber, SettingsFile(..), corsAllowedOrigins, fc_cors, fc_cookie_settings, microServicesProxyStatus)
import Gargantext.Database.Prelude qualified as DB
import Gargantext.MicroServices.ReverseProxy (microServicesProxyApp)
import Gargantext.Prelude hiding (putStrLn, to)
......@@ -205,7 +205,7 @@ makeApp env = do
where
cfg :: Servant.Context AuthContext
cfg = env ^. env_jwt_settings
:. env ^. settings . cookieSettings
:. env ^. env_config . gc_frontend_config . fc_cookie_settings
:. EmptyContext
---------------------------------------------------------------------
......
......@@ -42,7 +42,6 @@ import Gargantext.Utils.Jobs.Monad qualified as Jobs
import Gargantext.Utils.Jobs.Queue qualified as Jobs
import Gargantext.Utils.Jobs.Settings qualified as Jobs
import Network.HTTP.Client.TLS (newTlsManager)
import Servant.Auth.Server (CookieSettings(..), XsrfCookieSettings(..), defaultCookieSettings, defaultXsrfCookieSettings)
import Servant.Client (parseBaseUrl)
import Servant.Job.Async (newJobEnv, defaultSettings)
import System.Directory (renameFile)
......@@ -60,12 +59,8 @@ devSettings =
{ -- _corsSettings = _gargCorsSettings
-- , _microservicesSettings = _gargMicroServicesSettings
-- , _dbServer = "localhost"
_sendLoginEmails = LogEmailToConsole
, _scrapydUrl = fromMaybe (panicTrace "Invalid scrapy URL") $ parseBaseUrl "http://localhost:6800"
, _cookieSettings = defaultCookieSettings { cookieXsrfSetting = Just xsrfCookieSetting } -- TODO-SECURITY tune
_scrapydUrl = fromMaybe (panicTrace "Invalid scrapy URL") $ parseBaseUrl "http://localhost:6800"
}
where
xsrfCookieSetting = defaultXsrfCookieSettings { xsrfExcludeGet = True }
{- NOT USED YET
import System.Environment (lookupEnv)
......
......@@ -3,25 +3,16 @@
module Gargantext.API.Admin.Types where
import Control.Lens
import GHC.Enum
import Gargantext.Prelude
import Servant.Auth.Server (CookieSettings(..))
import Servant.Client (BaseUrl)
data SendEmailType = SendEmailViaAws
| LogEmailToConsole
| WriteEmailToFile
deriving (Show, Read, Enum, Bounded, Generic)
data Settings = Settings
{
-- , _dbServer :: Text
-- ^ this is not used yet
_cookieSettings :: !CookieSettings
, _sendLoginEmails :: !SendEmailType
, _scrapydUrl :: !BaseUrl
_scrapydUrl :: !BaseUrl
}
makeLenses ''Settings
......
......@@ -9,8 +9,6 @@ Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Core.Config.Ini.Mail (
-- * Types
GargMail(..)
......@@ -20,21 +18,13 @@ module Gargantext.Core.Config.Ini.Mail (
-- * Utility functions
, gargMail
, readConfig
-- * Lenses
, mc_mail_from
, mc_mail_host
, mc_mail_login_type
, mc_mail_password
, mc_mail_port
, mc_mail_user
)
where
import Data.Maybe
import Data.Text (unpack)
import Gargantext.Core.Config.Ini.Ini (readIniFile', val)
import Gargantext.Core.Config.Mail (LoginType(..), MailConfig(..))
import Gargantext.Core.Config.Mail (LoginType(..), MailConfig(..), SendEmailType(LogEmailToConsole))
import Gargantext.Prelude
import Network.Mail.Mime (plainPart)
import Network.Mail.SMTP hiding (htmlPart, STARTTLS)
......@@ -55,6 +45,7 @@ readConfig fp = do
, _mc_mail_from = cs $ val' "MAIL_FROM"
, _mc_mail_password = cs $ val' "MAIL_PASSWORD"
, _mc_mail_login_type = read $ cs $ val' "MAIL_LOGIN_TYPE"
, _mc_send_login_emails = LogEmailToConsole
}
......@@ -84,4 +75,3 @@ gargMail (MailConfig {..}) (GargMail { .. }) = do
cc = []
bcc = []
makeLenses ''MailConfig
......@@ -15,6 +15,7 @@ module Gargantext.Core.Config.Mail (
-- * Types
GargMail(..)
, LoginType(..)
, SendEmailType(..)
, MailConfig(..)
-- * Utility functions
......@@ -27,6 +28,7 @@ module Gargantext.Core.Config.Mail (
, mc_mail_password
, mc_mail_port
, mc_mail_user
, mc_send_login_emails
)
where
......@@ -47,7 +49,6 @@ type Name = Text
data LoginType = NoAuth | Normal | SSL | TLS | STARTTLS
deriving (Generic, Eq, Show, Read)
instance FromValue LoginType where
fromValue (Toml.Text' _ t) =
case t of
......@@ -61,12 +62,20 @@ instance FromValue LoginType where
instance ToValue LoginType where
toValue v = toValue (show v :: Text)
data SendEmailType = SendEmailViaAws
| LogEmailToConsole
| WriteEmailToFile
deriving (Show, Read, Enum, Bounded, Generic)
data MailConfig = MailConfig { _mc_mail_host :: !T.Text
, _mc_mail_port :: !PortNumber
, _mc_mail_user :: !T.Text
, _mc_mail_password :: !T.Text
, _mc_mail_login_type :: !LoginType
, _mc_mail_from :: !T.Text
, _mc_send_login_emails :: !SendEmailType
}
deriving (Generic, Show)
instance FromValue MailConfig where
......@@ -77,6 +86,7 @@ instance FromValue MailConfig where
_mc_mail_password <- reqKey "password"
_mc_mail_login_type <- reqKey "login_type"
_mc_mail_from <- reqKey "from"
let _mc_send_login_emails = LogEmailToConsole
return $ MailConfig { _mc_mail_port = fromIntegral port, .. }
instance ToValue MailConfig where
toValue = defaultTableToValue
......
......@@ -33,6 +33,8 @@ module Gargantext.Core.Config.Types
, fc_cors
, fc_microservices
, fc_appPort
, fc_cookie_settings
, defaultCookieSettings
, MicroServicesProxyStatus(..)
, microServicesProxyStatus
, JobsConfig(..)
......@@ -59,7 +61,8 @@ import Control.Monad.Fail (fail)
import Data.Text qualified as T
import Database.PostgreSQL.Simple qualified as PGS
import Gargantext.Prelude
import Servant.Auth.Server (JWTSettings, defaultJWTSettings, readKey, writeKey)
import Servant.Auth.Server (CookieSettings(..), JWTSettings, XsrfCookieSettings(..), defaultJWTSettings, readKey, writeKey)
import Servant.Auth.Server qualified as SAuth
import Servant.Client.Core (BaseUrl, parseBaseUrl, showBaseUrl)
import System.Directory (doesFileExist)
import Toml
......@@ -189,14 +192,20 @@ makeLenses ''FramesConfig
type PortNumber = Int
defaultCookieSettings :: CookieSettings
defaultCookieSettings = SAuth.defaultCookieSettings { cookieXsrfSetting = Just xsrfCookieSetting } -- TODO-SECURITY tune
where
xsrfCookieSetting = SAuth.defaultXsrfCookieSettings { xsrfExcludeGet = True }
-- TODO jwtSettings = defaultJWTSettings
data FrontendConfig =
FrontendConfig { _fc_url :: !Text
, _fc_backend_name :: !Text
FrontendConfig { _fc_url :: !Text
, _fc_backend_name :: !Text
, _fc_url_backend_api :: !Text
, _fc_cors :: !CORSSettings
, _fc_microservices :: !MicroServicesSettings
, _fc_appPort :: !PortNumber
, _fc_cors :: !CORSSettings
, _fc_microservices :: !MicroServicesSettings
, _fc_appPort :: !PortNumber
, _fc_cookie_settings :: !CookieSettings
}
deriving (Generic, Show)
instance FromValue FrontendConfig where
......@@ -207,7 +216,7 @@ instance FromValue FrontendConfig where
_fc_cors <- reqKey "cors"
_fc_microservices <- reqKey "microservices"
let _fc_appPort = 3000
return $ FrontendConfig { .. }
return $ FrontendConfig { _fc_cookie_settings = defaultCookieSettings, .. }
instance ToValue FrontendConfig where
toValue = defaultTableToValue
instance ToTable FrontendConfig where
......
......@@ -30,13 +30,12 @@ import Data.Text.Encoding qualified as TE
import GHC.Generics
import Gargantext.API.Admin.Auth.Types (AuthContext)
import Gargantext.API.Admin.EnvTypes
import Gargantext.API.Admin.Types
import Gargantext.API.Node.ShareURL qualified as Share
import Gargantext.API.Routes.Named.Private
import Gargantext.API.Routes.Named.Share (ShareLink(..))
import Gargantext.API.ThrowAll (throwAllRoutes)
import Gargantext.Core.Config (gc_frames, mkProxyUrl, hasConfig)
import Gargantext.Core.Config.Types (f_write_url)
import Gargantext.Core.Config (gc_frames, gc_frontend_config, mkProxyUrl, hasConfig)
import Gargantext.Core.Config.Types (f_write_url, fc_cookie_settings)
import Gargantext.Database.Admin.Types.Node (NodeType(..), NodeId (..))
import Gargantext.Prelude hiding (Handler)
import Network.HTTP.ReverseProxy
......@@ -158,7 +157,7 @@ microServicesProxyApp cache env = genericServeTWithContext identity (server cach
where
cfg :: Context AuthContext
cfg = env ^. env_jwt_settings
:. env ^. settings . cookieSettings
:. env ^. env_config . gc_frontend_config . fc_cookie_settings
:. EmptyContext
server :: ProxyCache -> Env -> ReverseProxyAPI (AsServerT Handler)
......
......@@ -38,7 +38,7 @@ import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude (HasConnectionPool(..))
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Core.Config
import Gargantext.Core.Config.Mail (MailConfig(..), LoginType(NoAuth))
import Gargantext.Core.Config.Mail (MailConfig(..), LoginType(NoAuth), SendEmailType(LogEmailToConsole))
import Gargantext.System.Logging (HasLogger(..), Logger, MonadLogger(..))
import Gargantext.Utils.Jobs
import Network.URI (parseURI)
......@@ -111,12 +111,13 @@ instance HasSettings TestEnv where
settings = to test_settings
instance HasMail TestEnv where
mailSettings = to $ const (MailConfig { _mc_mail_host = "localhost"
, _mc_mail_port = 25
, _mc_mail_user = "test"
, _mc_mail_from = "test@localhost"
, _mc_mail_password = "test"
, _mc_mail_login_type = NoAuth })
mailSettings = to $ const (MailConfig { _mc_mail_host = "localhost"
, _mc_mail_port = 25
, _mc_mail_user = "test"
, _mc_mail_from = "test@localhost"
, _mc_mail_password = "test"
, _mc_mail_login_type = NoAuth
, _mc_send_login_emails = LogEmailToConsole })
instance HasNodeStoryEnv TestEnv where
hasNodeStory = to test_nodeStory
......
......@@ -288,6 +288,7 @@ newTestEnv = do
, _gc_jobs = Prelude.error "gc_jobs not needed, but forced somewhere (check StrictData)"
, _gc_secrets = Prelude.error "gc_secrets not needed, but forced somewhere (check StrictData)"
, _gc_apis = Prelude.error "gc_apis not needed, but forced somewhere (check StrictData)"
, _gc_log_level = Prelude.error "gc_log_level not needed, but forced somewhere (check StrictData)"
}
pure $ Env
{ _env_settings = Prelude.error "env_settings not needed, but forced somewhere (check StrictData)"
......@@ -301,6 +302,7 @@ newTestEnv = do
, _env_config
, _env_central_exchange = Prelude.error "central exchange not needed, but forced somewhere (check StrictData)"
, _env_dispatcher = Prelude.error "dispatcher not needed, but forced somewhere (check StrictData)"
, _env_jwt_settings = Prelude.error "jwt_settings not needed, but forced somewherer (check StrictData)"
}
testFetchJobStatus :: IO ()
......
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