[config] more toml fixes: fc internal/external urls added

parent 8cde94d7
Pipeline #7731 passed with stages
in 55 minutes and 50 seconds
...@@ -101,8 +101,9 @@ convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo = ...@@ -101,8 +101,9 @@ convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo =
mkFrontendConfig :: Ini.GargConfig -> CTypes.FrontendConfig mkFrontendConfig :: Ini.GargConfig -> CTypes.FrontendConfig
mkFrontendConfig (Ini.GargConfig { .. }) = mkFrontendConfig (Ini.GargConfig { .. }) =
CTypes.FrontendConfig { _fc_url CTypes.FrontendConfig { _fc_external_url = _fc_url
, _fc_internal_url = _fc_url , _fc_internal_url = _fc_url
, _fc_directory = "./purescript-gargantext/dist"
, _fc_backend_name = _gc_backend_name , _fc_backend_name = _gc_backend_name
, _fc_cors , _fc_cors
, _fc_microservices , _fc_microservices
......
[frontend] [frontend]
# Main url serving the FrontEnd (public URL) # Main url serving the FrontEnd (public URL)
url = "http://localhost:8008" external_url = "http://localhost:8008"
# in case this is behind a reverse proxy
# host/port where the GarganText server will bind to
internal_url = "http://localhost:8008" internal_url = "http://localhost:8008"
# Location of the frontend code. This will be served at the root of
# the path (e.g. index.html)
directory = "./purescript-gargantext/dist"
backend_name = "localhost" backend_name = "localhost"
jwt_settings = "TODO" jwt_settings = "TODO"
......
...@@ -16,9 +16,10 @@ Loads all static file for the front-end. ...@@ -16,9 +16,10 @@ Loads all static file for the front-end.
--------------------------------------------------------------------- ---------------------------------------------------------------------
module Gargantext.API.Admin.FrontEnd where module Gargantext.API.Admin.FrontEnd where
import GHC.IO (FilePath)
import Servant import Servant
type FrontEndAPI = Raw type FrontEndAPI = Raw
frontEndServer :: Server FrontEndAPI frontEndServer :: FilePath -> Server FrontEndAPI
frontEndServer = serveDirectoryFileServer "./purescript-gargantext/dist" frontEndServer path = serveDirectoryFileServer path
...@@ -24,7 +24,7 @@ import Gargantext.API.Swagger (openApiDoc) ...@@ -24,7 +24,7 @@ import Gargantext.API.Swagger (openApiDoc)
import Gargantext.API.ThrowAll (serverPrivateGargAPI) import Gargantext.API.ThrowAll (serverPrivateGargAPI)
import Gargantext.Core.Notifications.Dispatcher.WebSocket qualified as Dispatcher import Gargantext.Core.Notifications.Dispatcher.WebSocket qualified as Dispatcher
import Gargantext.Core.Config (gc_frontend_config, hasConfig) import Gargantext.Core.Config (gc_frontend_config, hasConfig)
import Gargantext.Core.Config.Types (fc_url) import Gargantext.Core.Config.Types (fc_directory, fc_external_url)
import Gargantext.Prelude hiding (Handler, catch) import Gargantext.Prelude hiding (Handler, catch)
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
...@@ -40,7 +40,7 @@ serverGargAPI env ...@@ -40,7 +40,7 @@ serverGargAPI env
, gargForgotPasswordAsyncAPI = forgotPasswordAsync , gargForgotPasswordAsyncAPI = forgotPasswordAsync
, gargVersionAPI = gargVersion , gargVersionAPI = gargVersion
, gargPrivateAPI = serverPrivateGargAPI , gargPrivateAPI = serverPrivateGargAPI
, gargPublicAPI = serverPublicGargAPI (env ^. hasConfig . gc_frontend_config . fc_url) , gargPublicAPI = serverPublicGargAPI (env ^. hasConfig . gc_frontend_config . fc_external_url)
} }
where where
gargVersion :: GargVersion (AsServerT (GargM Env BackendInternalError)) gargVersion :: GargVersion (AsServerT (GargM Env BackendInternalError))
...@@ -66,7 +66,7 @@ server env = ...@@ -66,7 +66,7 @@ server env =
-- (Proxy :: Proxy AuthContext) -- (Proxy :: Proxy AuthContext)
(transformJSON errScheme) (transformJSON errScheme)
Dispatcher.wsServer Dispatcher.wsServer
, frontendAPI = frontEndServer , frontendAPI = frontEndServer (env ^. hasConfig . gc_frontend_config . fc_directory)
} }
where where
transformJSON :: forall a. GargErrorScheme -> GargM Env BackendInternalError a -> Handler a transformJSON :: forall a. GargErrorScheme -> GargM Env BackendInternalError a -> Handler a
......
...@@ -143,7 +143,7 @@ instance ToTable GargConfig where ...@@ -143,7 +143,7 @@ instance ToTable GargConfig where
mkProxyUrl :: GargConfig -> BaseUrl mkProxyUrl :: GargConfig -> BaseUrl
mkProxyUrl GargConfig{ _gc_frontend_config = cfg } = mkProxyUrl GargConfig{ _gc_frontend_config = cfg } =
(_fc_url cfg) { baseUrlPort = _msProxyPort $ _fc_microservices cfg } (_fc_external_url cfg) { baseUrlPort = _msProxyPort $ _fc_microservices cfg }
class HasConfig env where class HasConfig env where
......
...@@ -27,9 +27,10 @@ module Gargantext.Core.Config.Types ...@@ -27,9 +27,10 @@ module Gargantext.Core.Config.Types
, f_istex_url , f_istex_url
, PortNumber , PortNumber
, FrontendConfig(..) , FrontendConfig(..)
, fc_url , fc_external_url
, fc_internal_url , fc_internal_url
, fc_backend_name , fc_backend_name
, fc_directory
, fc_cors , fc_cors
, fc_microservices , fc_microservices
, fc_cookie_settings , fc_cookie_settings
...@@ -199,8 +200,9 @@ defaultCookieSettings = SAuth.defaultCookieSettings { cookieXsrfSetting = Just x ...@@ -199,8 +200,9 @@ defaultCookieSettings = SAuth.defaultCookieSettings { cookieXsrfSetting = Just x
-- TODO jwtSettings = defaultJWTSettings -- TODO jwtSettings = defaultJWTSettings
data FrontendConfig = data FrontendConfig =
FrontendConfig { _fc_url :: !BaseUrl FrontendConfig { _fc_external_url :: !BaseUrl
, _fc_internal_url :: !BaseUrl , _fc_internal_url :: !BaseUrl
, _fc_directory :: !FilePath
, _fc_backend_name :: !Text , _fc_backend_name :: !Text
, _fc_cors :: !CORSSettings , _fc_cors :: !CORSSettings
, _fc_microservices :: !MicroServicesSettings , _fc_microservices :: !MicroServicesSettings
...@@ -209,16 +211,17 @@ data FrontendConfig = ...@@ -209,16 +211,17 @@ data FrontendConfig =
deriving (Generic, Show) deriving (Generic, Show)
instance FromValue FrontendConfig where instance FromValue FrontendConfig where
fromValue = parseTableFromValue $ do fromValue = parseTableFromValue $ do
_fc_url_txt <- reqKey "url" _fc_external_url_txt <- reqKey "external_url"
_fc_url <- _fc_external_url <-
case parseBaseUrl (T.unpack _fc_url_txt) of case parseBaseUrl (T.unpack _fc_external_url_txt) of
Nothing -> fail "cannot parse fc_url" Nothing -> fail "cannot parse fc_external_url"
Just b -> pure b Just b -> pure b
_fc_internal_url_txt <- reqKey "internal_url" _fc_internal_url_txt <- reqKey "internal_url"
_fc_internal_url <- _fc_internal_url <-
case parseBaseUrl (T.unpack _fc_internal_url_txt) of case parseBaseUrl (T.unpack _fc_internal_url_txt) of
Nothing -> fail "cannot parse fc_internal_url" Nothing -> fail "cannot parse fc_internal_url"
Just b -> pure b Just b -> pure b
_fc_directory <- reqKey "directory"
_fc_backend_name <- reqKey "backend_name" _fc_backend_name <- reqKey "backend_name"
_fc_cors <- reqKey "cors" _fc_cors <- reqKey "cors"
_fc_microservices <- reqKey "microservices" _fc_microservices <- reqKey "microservices"
...@@ -228,8 +231,9 @@ instance ToValue FrontendConfig where ...@@ -228,8 +231,9 @@ instance ToValue FrontendConfig where
toValue = defaultTableToValue toValue = defaultTableToValue
instance ToTable FrontendConfig where instance ToTable FrontendConfig where
toTable (FrontendConfig { .. }) = table toTable (FrontendConfig { .. }) = table
[ "url" .= (T.pack $ showBaseUrl _fc_url) [ "external_url" .= (T.pack $ showBaseUrl _fc_external_url)
, "internal_url" .= (T.pack $ showBaseUrl _fc_internal_url) , "internal_url" .= (T.pack $ showBaseUrl _fc_internal_url)
, "directory" .= _fc_directory
, "backend_name" .= _fc_backend_name , "backend_name" .= _fc_backend_name
, "cors" .= _fc_cors , "cors" .= _fc_cors
, "microservices" .= _fc_microservices ] , "microservices" .= _fc_microservices ]
...@@ -237,7 +241,7 @@ instance ToTable FrontendConfig where ...@@ -237,7 +241,7 @@ instance ToTable FrontendConfig where
makeLenses ''FrontendConfig makeLenses ''FrontendConfig
getPublicUrl :: FrontendConfig -> Text getPublicUrl :: FrontendConfig -> Text
getPublicUrl (FrontendConfig { .. }) = T.pack $ showBaseUrl _fc_url getPublicUrl (FrontendConfig { .. }) = T.pack $ showBaseUrl _fc_external_url
data MicroServicesProxyStatus data MicroServicesProxyStatus
= PXY_enabled PortNumber = PXY_enabled PortNumber
......
[frontend] [frontend]
url = "http://localhost" external_url = "http://localhost"
internal_url = "http://localhost" internal_url = "http://localhost"
directory = "./purescript-gargantext/dist"
backend_name = "localhost" backend_name = "localhost"
jwt_settings = "TODO" jwt_settings = "TODO"
......
...@@ -24,7 +24,7 @@ import Gargantext.API.Admin.EnvTypes (Env (..), env_dispatcher) ...@@ -24,7 +24,7 @@ import Gargantext.API.Admin.EnvTypes (Env (..), env_dispatcher)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.Config hiding (jwtSettings) import Gargantext.Core.Config hiding (jwtSettings)
import Gargantext.Core.Config.Types (jwtSettings, fc_url, fc_internal_url) import Gargantext.Core.Config.Types (jwtSettings, fc_external_url, fc_internal_url)
import Gargantext.Core.Notifications (withNotifications) import Gargantext.Core.Notifications (withNotifications)
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Database.Action.Flow import Gargantext.Database.Action.Flow
...@@ -74,7 +74,7 @@ newTestEnv testEnv logger port = do ...@@ -74,7 +74,7 @@ newTestEnv testEnv logger port = do
!manager_env <- newTlsManager !manager_env <- newTlsManager
let config_env = test_config testEnv let config_env = test_config testEnv
& (gc_frontend_config . fc_url) %~ (\b -> b { baseUrlPort = port }) & (gc_frontend_config . fc_external_url) %~ (\b -> b { baseUrlPort = port })
& (gc_frontend_config . fc_internal_url) %~ (\b -> b { baseUrlPort = port }) & (gc_frontend_config . fc_internal_url) %~ (\b -> b { baseUrlPort = port })
-- dbParam <- pure $ testEnvToPgConnectionInfo testEnv -- dbParam <- pure $ testEnvToPgConnectionInfo testEnv
-- !pool <- newPool dbParam -- !pool <- newPool dbParam
......
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