[BREAKING] refactoring of fc_url

Now it is required to specify port in `frontend.url`.

The `-p` port flag was removed from CLI server.

Related to
#465
parent 71f84c4c
Pipeline #7545 passed with stages
in 48 minutes and 20 seconds
......@@ -102,12 +102,11 @@ convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo =
mkFrontendConfig :: Ini.GargConfig -> CTypes.FrontendConfig
mkFrontendConfig (Ini.GargConfig { .. }) =
CTypes.FrontendConfig { _fc_url = _gc_url
CTypes.FrontendConfig { _fc_url
, _fc_backend_name = _gc_backend_name
, _fc_url_backend_api = _gc_url_backend_api
, _fc_cors
, _fc_microservices
, _fc_appPort = 3000
, _fc_cookie_settings = CTypes.defaultCookieSettings }
where
_fc_cors = CTypes.CORSSettings { _corsAllowedOrigins = [
......@@ -136,6 +135,10 @@ mkFrontendConfig (Ini.GargConfig { .. }) =
case parseBaseUrl (T.unpack url) of
Nothing -> panicTrace $ "Cannot parse base url for: " <> url
Just b -> CTypes.CORSOrigin b
_fc_url =
case parseBaseUrl (T.unpack _gc_url) of
Nothing -> panicTrace $ "Cannot parse base url for: " <> _gc_url
Just b -> b
defaultNotificationsConfig :: CTypes.NotificationsConfig
defaultNotificationsConfig =
......
......@@ -77,13 +77,11 @@ serverParser = hsubparser (
start_p :: Parser CLIServer
start_p = fmap CLIS_start $ ServerArgs
<$> mode_p
<*> port_p
<*> settings_p
start_all_p :: Parser CLIServer
start_all_p = fmap CLIS_startAll $ ServerArgs
<$> mode_p
<*> port_p
<*> settings_p
mode_p :: Parser Mode
......@@ -92,21 +90,13 @@ mode_p = option auto ( long "mode"
<> metavar "M"
<> help "Possible modes: Dev | Mock | Prod" )
port_p :: Parser Int
port_p = option auto ( long "port"
<> short 'p'
<> metavar "P"
<> showDefault
<> value 8008
<> help "Port" )
version_p :: Parser CLIServer
version_p = pure CLIS_version
startServerCLI :: Logger IO -> ServerArgs -> IO ()
startServerCLI ioLogger (ServerArgs { .. }) = do
logMsg ioLogger INFO $ "starting server, mode: " <> show server_mode <> ", port: " <> show server_port <> ", config: " <> _SettingsFile server_toml
logMsg ioLogger INFO $ "starting server, mode: " <> show server_mode <> ", config: " <> _SettingsFile server_toml
-- Sets the locale to avoid encoding issues like in #284.
setLocaleEncoding utf8
......@@ -114,4 +104,4 @@ startServerCLI ioLogger (ServerArgs { .. }) = do
logMsg ioLogger ERROR "Mock mode not supported!"
exitFailure
startGargantext server_mode server_port server_toml
startGargantext server_mode server_toml
......@@ -100,7 +100,6 @@ data CLIServer
data ServerArgs = ServerArgs
{ server_mode :: !Mode
, server_port :: !Int
, server_toml :: !SettingsFile }
deriving (Show, Eq)
......
[frontend]
# Main url serving the FrontEnd
url = "http://localhost"
url = "http://localhost:8008"
backend_name = "localhost"
# Main API url serving the BackEnd
# Main API url serving the BackEnd. This is currently used only for
# the public API endpoints.
url_backend_api = "http://localhost:8008/api/v1.0"
jwt_settings = "TODO"
......
# https://nix.dev/tutorials/first-steps/towards-reproducibility-pinning-nixpkgs.html
{ pkgs ? import (if builtins.elem builtins.currentSystem ["x86_64-darwin" "aarch64-darwin"]
then ./pinned-25.05.darwin.nix
else ./pinned-25.05.nix) {} }:
rec {
inherit pkgs;
ghc966 = pkgs.haskell.compiler.ghc966;
cabal_install = pkgs.haskell.lib.compose.justStaticExecutables pkgs.haskell.packages.ghc966.cabal-install;
ghcVersion = "ghc966";
gargGhc = pkgs.haskell.compiler.${ghcVersion};
cabal_install = pkgs.haskell.lib.compose.justStaticExecutables pkgs.haskell.packages.${ghcVersion}.cabal-install;
graphviz = pkgs.callPackage ./graphviz.nix {};
igraph_0_10_4 = pkgs.callPackage ./igraph.nix {};
corenlp = pkgs.callPackage ./corenlp.nix { }; # 4.5.8
cabal2stack = pkgs.callPackage ./cabal2stack.nix { ghc = ghc966; };
corenlp = pkgs.callPackage ./corenlp.nix { }; # 4.5.9
cabal2stack = pkgs.callPackage ./cabal2stack.nix { ghc = gargGhc; };
nng_notls = pkgs.nng.overrideAttrs (old: {
cmakeFlags = (old.cmakeFlags or []) ++ [ "-DNNG_ENABLE_TLS=OFF" ];
});
hsBuildInputs = [
ghc966
gargGhc
cabal_install
pkgs.haskellPackages.alex
pkgs.haskellPackages.happy
......
......@@ -49,7 +49,7 @@ import Gargantext.API.Routes.Named (API)
import Gargantext.API.Routes.Named.EKG (EkgAPI)
import Gargantext.API.Server.Named (server)
import Gargantext.Core.Config
import Gargantext.Core.Config.Types (CORSOrigin(..), CORSSettings, MicroServicesProxyStatus(..), NotificationsConfig(..), PortNumber, SettingsFile(..), corsAllowedOrigins, fc_appPort, fc_cors, fc_cookie_settings, microServicesProxyStatus)
import Gargantext.Core.Config.Types (CORSOrigin(..), CORSSettings, MicroServicesProxyStatus(..), NotificationsConfig(..), PortNumber, SettingsFile(..), corsAllowedOrigins, fc_cors, fc_cookie_settings, fc_url, microServicesProxyStatus)
import Gargantext.Core.Config.Utils (readConfig)
import Gargantext.Core.Notifications (withNotifications)
import Gargantext.Database.Prelude qualified as DB
......@@ -62,21 +62,20 @@ import Network.Wai.Handler.Warp hiding (defaultSettings)
import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger (logStdout)
import Servant hiding (Header)
import Servant.Client.Core.BaseUrl (showBaseUrl)
import Servant.Client.Core.BaseUrl (showBaseUrl, baseUrlPort)
import System.Clock qualified as Clock
import System.Cron.Schedule qualified as Cron
-- | startGargantext takes as parameters port number and Toml file.
startGargantext :: Mode -> PortNumber -> SettingsFile -> IO ()
startGargantext mode port sf@(SettingsFile settingsFile) = do
config <- readConfig sf <&> (gc_frontend_config . fc_appPort) .~ port
startGargantext :: Mode -> SettingsFile -> IO ()
startGargantext mode sf@(SettingsFile settingsFile) = do
config <- readConfig sf
withLoggerIO (config ^. gc_logging) $ \logger -> do
when (port /= config ^. gc_frontend_config . fc_appPort) $
panicTrace "TODO: conflicting settings of port"
withNotifications config $ \dispatcher -> do
env <- newEnv logger config dispatcher
let fc = env ^. env_config . gc_frontend_config
let proxyStatus = microServicesProxyStatus fc
let port = baseUrlPort (fc ^. fc_url)
runDbCheck env
startupInfo config port proxyStatus
app <- makeApp env
......
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
......@@ -10,7 +10,7 @@ import Data.Validity qualified as V
import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Share qualified as Named
import Gargantext.Core.Config (GargConfig, gc_frontend_config, HasConfig(hasConfig))
import Gargantext.Core.Config.Types (fc_appPort, fc_url)
import Gargantext.Core.Config.Types (getPublicUrl)
import Gargantext.Core.Types (NodeType, NodeId, unNodeId, _ValidationError)
import Gargantext.Database.Prelude (IsDBEnvExtra)
import Gargantext.Prelude
......@@ -37,18 +37,21 @@ get_url :: Maybe NodeType
-> GargConfig
-> Either String Named.ShareLink
get_url nt id gc = do
let urlHost = T.unpack $ gc ^. gc_frontend_config . fc_url
let urlPort = gc ^. gc_frontend_config . fc_appPort
let fc = gc ^. gc_frontend_config
-- let urlHost = T.unpack $ gc ^. gc_frontend_config . fc_url
-- let urlPort = gc ^. gc_frontend_config . fc_appPort
t <- maybe (Left "Invalid node Type") Right nt
i <- maybe (Left "Invalid node ID") Right id
let sharePart = "/#/share/" <> show t <> "/" <> show (unNodeId i)
-- Include the port the server is running on if this is
-- localhost, so that share URLs would work out of the box.
let !rawURL
| "localhost" `isInfixOf` urlHost
= urlHost <> ":" <> show urlPort <> "/#/share/" <> show t <> "/" <> show (unNodeId i)
| otherwise
= urlHost <> "/#/share/" <> show t <> "/" <> show (unNodeId i)
let !rawURL = T.unpack $ (getPublicUrl fc) <> sharePart
-- | "localhost" `isInfixOf` urlHost
-- = urlHost <> ":" <> show urlPort <> "/#/share/" <> show t <> "/" <> show (unNodeId i)
-- | otherwise
-- = urlHost <> "/#/share/" <> show t <> "/" <> show (unNodeId i)
maybe (Left $ "Couldn't construct a valid share URL from '" <> rawURL <> "'")
(Right . Named.ShareLink)
(parseURI rawURL)
......@@ -53,7 +53,7 @@ import Gargantext.Core.Config.Worker (WorkerSettings)
import Gargantext.Prelude
import Network.HTTP.Client qualified as HTTP
import Servant.Auth.Server (JWTSettings)
import Servant.Client (BaseUrl(..), Scheme(Http), parseBaseUrl)
import Servant.Client (BaseUrl(..))
import Toml.Schema
import Toml.Schema.FromValue (typeError)
......@@ -142,10 +142,8 @@ instance ToTable GargConfig where
mkProxyUrl :: GargConfig -> BaseUrl
mkProxyUrl GargConfig{..} =
case parseBaseUrl (T.unpack $ _fc_url _gc_frontend_config) of
Nothing -> BaseUrl Http "localhost" 80 ""
Just bh -> bh { baseUrlPort = _msProxyPort $ _fc_microservices _gc_frontend_config }
mkProxyUrl GargConfig{ _gc_frontend_config = cfg } =
(_fc_url cfg) { baseUrlPort = _msProxyPort $ _fc_microservices cfg }
class HasConfig env where
......
......@@ -32,8 +32,8 @@ module Gargantext.Core.Config.Types
, fc_url_backend_api
, fc_cors
, fc_microservices
, fc_appPort
, fc_cookie_settings
, getPublicUrl
, defaultCookieSettings
, MicroServicesProxyStatus(..)
, microServicesProxyStatus
......@@ -63,7 +63,7 @@ import Database.PostgreSQL.Simple qualified as PGS
import Gargantext.Prelude
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 Servant.Client.Core (BaseUrl(..), parseBaseUrl, showBaseUrl)
import System.Directory (doesFileExist)
import Toml
import Toml.Schema
......@@ -199,28 +199,31 @@ defaultCookieSettings = SAuth.defaultCookieSettings { cookieXsrfSetting = Just x
-- TODO jwtSettings = defaultJWTSettings
data FrontendConfig =
FrontendConfig { _fc_url :: !Text
FrontendConfig { _fc_url :: !BaseUrl
, _fc_backend_name :: !Text
, _fc_url_backend_api :: !Text
, _fc_cors :: !CORSSettings
, _fc_microservices :: !MicroServicesSettings
, _fc_appPort :: !PortNumber
, _fc_cookie_settings :: !CookieSettings
}
deriving (Generic, Show)
instance FromValue FrontendConfig where
fromValue = parseTableFromValue $ do
_fc_url <- reqKey "url"
_fc_url_txt <- reqKey "url"
_fc_url <-
case parseBaseUrl (T.unpack _fc_url_txt) of
Nothing -> fail "cannot parse fc_url"
Just b -> pure b
_fc_backend_name <- reqKey "backend_name"
_fc_url_backend_api <- reqKey "url_backend_api"
_fc_cors <- reqKey "cors"
_fc_microservices <- reqKey "microservices"
let _fc_appPort = 3000
return $ FrontendConfig { _fc_cookie_settings = defaultCookieSettings, .. }
instance ToValue FrontendConfig where
toValue = defaultTableToValue
instance ToTable FrontendConfig where
toTable (FrontendConfig { .. }) = table [ "url" .= _fc_url
toTable (FrontendConfig { .. }) = table [ "url" .= (T.pack $ showBaseUrl _fc_url)
, "backend_name" .= _fc_backend_name
, "url_backend_api" .= _fc_url_backend_api
, "cors" .= _fc_cors
......@@ -228,6 +231,9 @@ instance ToTable FrontendConfig where
makeLenses ''FrontendConfig
getPublicUrl :: FrontendConfig -> Text
getPublicUrl (FrontendConfig { .. }) = T.pack $ showBaseUrl _fc_url
data MicroServicesProxyStatus
= PXY_enabled PortNumber
| PXY_disabled
......
......@@ -16,7 +16,7 @@ import Control.Monad.Trans.Control (MonadBaseControl)
import Data.List qualified as List
import Data.Text (splitOn)
import Gargantext.Core.Config (gc_frontend_config, HasConfig(..))
import Gargantext.Core.Config.Types (fc_url, fc_backend_name)
import Gargantext.Core.Config.Types (fc_backend_name, getPublicUrl)
import Gargantext.Core.Config.Mail (gargMail, GargMail(..), MailConfig)
import Gargantext.Core.Types.Individu
import Gargantext.Database.Schema.User (UserLight(..))
......@@ -75,7 +75,7 @@ mail mailCfg model = do
(m,u) = email_to model
subject = email_subject model
body = emailWith (ServerAddress (view (gc_frontend_config . fc_backend_name) cfg)
(view (gc_frontend_config . fc_url) cfg)) model
(getPublicUrl $ view gc_frontend_config cfg)) model
liftBase $ gargMail mailCfg (GargMail { gm_to = m
, gm_name = Just u
, gm_subject = subject
......
......@@ -25,7 +25,7 @@ import Gargantext.API.Admin.EnvTypes (Env (..), env_dispatcher)
import Gargantext.API.Errors.Types
import Gargantext.API.Prelude
import Gargantext.Core.Config hiding (jwtSettings)
import Gargantext.Core.Config.Types (fc_appPort, jwtSettings)
import Gargantext.Core.Config.Types (jwtSettings, fc_url)
import Gargantext.Core.Notifications (withNotifications)
import Gargantext.Core.Types.Individu
import Gargantext.Database.Action.Flow
......@@ -38,7 +38,7 @@ import Gargantext.Database.Prelude ()
import Gargantext.Database.Query.Table.Node (getOrMkList)
import Gargantext.Database.Query.Tree.Root (MkCorpusUser(..))
import Gargantext.MicroServices.ReverseProxy (microServicesProxyApp)
import Gargantext.Prelude hiding (catches, Handler)
import Gargantext.Prelude hiding (catches, to, Handler)
import Gargantext.System.Logging
import Network.HTTP.Client.TLS (newTlsManager)
import Network.HTTP.Types
......@@ -49,6 +49,7 @@ import Network.Wai.Handler.Warp.Internal
import Network.WebSockets qualified as WS
import Prelude hiding (show)
import Servant.Auth.Client ()
import Servant.Client.Core (baseUrlPort)
import Test.Database.Setup (withTestDB)
import Test.Database.Types
import UnliftIO qualified
......@@ -73,7 +74,7 @@ newTestEnv :: TestEnv -> Logger (GargM Env BackendInternalError) -> Warp.Port ->
newTestEnv testEnv logger port = do
!manager_env <- newTlsManager
let config_env = test_config testEnv & (gc_frontend_config . fc_appPort) .~ port
let config_env = test_config testEnv & (gc_frontend_config . fc_url) %~ (\b -> b { baseUrlPort = port })
-- dbParam <- pure $ testEnvToPgConnectionInfo testEnv
-- !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