[server] some refactoring

parent 9f30d0b4
Pipeline #5651 canceled with stages
in 14 minutes and 1 second
...@@ -11,7 +11,6 @@ Script to start gargantext with different modes (Dev, Prod, Mock). ...@@ -11,7 +11,6 @@ Script to start gargantext with different modes (Dev, Prod, Mock).
-} -}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Strict #-} {-# LANGUAGE Strict #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
...@@ -22,16 +21,17 @@ Script to start gargantext with different modes (Dev, Prod, Mock). ...@@ -22,16 +21,17 @@ Script to start gargantext with different modes (Dev, Prod, Mock).
module Main where module Main where
import Data.Maybe (fromMaybe)
import Data.Text (unpack) import Data.Text (unpack)
import Data.Version (showVersion) import Data.Version (showVersion)
import GHC.IO.Encoding
import Gargantext.API (startGargantext) -- , startGargantextMock) import Gargantext.API (startGargantext) -- , startGargantextMock)
import Gargantext.API.Admin.EnvTypes import Gargantext.API.Admin.EnvTypes
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging import Gargantext.System.Logging
import GHC.IO.Encoding
import Options.Generic import Options.Generic
import Paths_gargantext qualified as PG -- cabal magic build module
import System.Exit (exitSuccess) import System.Exit (exitSuccess)
import qualified Paths_gargantext as PG -- cabal magic build module
instance ParseRecord Mode instance ParseRecord Mode
...@@ -69,9 +69,7 @@ main = withLogger () $ \ioLogger -> do ...@@ -69,9 +69,7 @@ main = withLogger () $ \ioLogger -> do
else else
return () return ()
--------------------------------------------------------------- ---------------------------------------------------------------
let myPort' = case myPort of let myPort' = fromMaybe 8008 myPort
Just p -> p
Nothing -> 8008
myIniFile' = case myIniFile of myIniFile' = case myIniFile of
Nothing -> panicTrace "[ERROR] gargantext.ini needed" Nothing -> panicTrace "[ERROR] gargantext.ini needed"
......
...@@ -27,41 +27,37 @@ Pouillard (who mainly made it). ...@@ -27,41 +27,37 @@ Pouillard (who mainly made it).
-} -}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.API module Gargantext.API
where where
import Control.Concurrent
import Control.Lens hiding (Level)
import Data.List (lookup) import Data.List (lookup)
import Data.Text (pack) import Data.Text (pack)
import Data.Text.Encoding qualified as TE import Data.Text.Encoding qualified as TE
import Data.Text.IO (putStrLn) import Data.Text.IO (putStrLn)
import Data.Validity
import Gargantext.API.Admin.Auth.Types (AuthContext) import Gargantext.API.Admin.Auth.Types (AuthContext)
import Gargantext.API.Admin.EnvTypes (Env, Mode(..)) import Gargantext.API.Admin.EnvTypes (Env, Mode(..))
import Gargantext.API.Admin.Settings (newEnv) import Gargantext.API.Admin.Settings (newEnv)
import Gargantext.API.Admin.Settings.CORS import Gargantext.API.Admin.Settings.CORS ( corsAllowedOrigins, CORSOrigin(_CORSOrigin), CORSSettings )
import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings, corsSettings) import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings, corsSettings)
import Gargantext.API.EKG import Gargantext.API.EKG ( ekgServer, newEkgStore, EkgAPI )
import Gargantext.API.Middleware (logStdoutDevSanitised) import Gargantext.API.Middleware (logStdoutDevSanitised)
import Gargantext.API.Routes import Gargantext.API.Routes ( API, GargAPI )
import Gargantext.API.Server (server) import Gargantext.API.Server (server)
import Gargantext.Database.Prelude qualified as DB import Gargantext.Database.Prelude qualified as DB
import Gargantext.Prelude hiding (putStrLn) import Gargantext.Prelude hiding (putStrLn)
import Gargantext.System.Logging import Gargantext.System.Logging ( withLoggerHoisted )
import Network.HTTP.Types hiding (Query) import Network.HTTP.Types ( methodDelete, methodGet, methodHead, methodOptions, methodPost, methodPut )
import Network.Wai import Network.Wai ( Middleware, Request(requestHeaders) )
import Network.Wai.Handler.Warp hiding (defaultSettings) import Network.Wai.Handler.Warp (run)
import Network.Wai.Middleware.Cors import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger import Network.Wai.Middleware.RequestLogger ( logStdout )
import Paths_gargantext (getDataDir) import Paths_gargantext (getDataDir)
import Servant hiding (Header) import Servant hiding (Header)
import System.Cron.Schedule qualified as Cron import System.Cron.Schedule qualified as Cron
import System.FilePath import System.FilePath ( (</>) )
-- | startGargantext takes as parameters port number and Ini file. -- | startGargantext takes as parameters port number and Ini file.
startGargantext :: Mode -> PortNumber -> FilePath -> IO () startGargantext :: Mode -> PortNumber -> FilePath -> IO ()
...@@ -79,7 +75,7 @@ startGargantext mode port file = withLoggerHoisted mode $ \logger -> do ...@@ -79,7 +75,7 @@ startGargantext mode port file = withLoggerHoisted mode $ \logger -> do
(\(_ :: SomeException) -> pure $ Right False) (\(_ :: SomeException) -> pure $ Right False)
case r of case r of
Right True -> pure () Right True -> pure ()
_ -> panicTrace $ _left -> panicTrace $
"You must run 'gargantext-init " <> pack file <> "You must run 'gargantext-init " <> pack file <>
"' before running gargantext-server (only the first time)." "' before running gargantext-server (only the first time)."
...@@ -131,7 +127,7 @@ fireWall req fw = do ...@@ -131,7 +127,7 @@ fireWall req fw = do
if origin == Just (encodeUtf8 "http://localhost:8008") if origin == Just (encodeUtf8 "http://localhost:8008")
&& host == Just (encodeUtf8 "localhost:3000") && host == Just (encodeUtf8 "localhost:3000")
|| (not $ unFireWall fw) || not (unFireWall fw)
then pure True then pure True
else pure False else pure False
...@@ -149,7 +145,7 @@ makeGargMiddleware crsSettings mode = do ...@@ -149,7 +145,7 @@ makeGargMiddleware crsSettings mode = do
} }
case mode of case mode of
Prod -> pure $ logStdout . corsMiddleware Prod -> pure $ logStdout . corsMiddleware
_ -> do _otherwise -> do
loggerMiddleware <- logStdoutDevSanitised loggerMiddleware <- logStdoutDevSanitised
pure $ loggerMiddleware . corsMiddleware pure $ loggerMiddleware . corsMiddleware
where 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