[websockets] add websocket to routes

Also, removed EKG (I don't know how to make it work with WS)
parent ca339d93
Pipeline #6053 failed with stages
in 6 minutes and 9 seconds
...@@ -58,10 +58,10 @@ import Network.Wai ...@@ -58,10 +58,10 @@ import Network.Wai
import Network.Wai.Handler.Warp hiding (defaultSettings) import Network.Wai.Handler.Warp hiding (defaultSettings)
import Network.Wai.Middleware.Cors import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger import Network.Wai.Middleware.RequestLogger
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 ()
...@@ -167,10 +167,11 @@ makeGargMiddleware crsSettings mode = do ...@@ -167,10 +167,11 @@ makeGargMiddleware crsSettings mode = do
makeApp :: Env -> IO Application makeApp :: Env -> IO Application
makeApp env = do makeApp env = do
serv <- server env serv <- server env
(ekgStore, ekgMid) <- newEkgStore api pure $ serveWithContext api cfg serv
ekgDir <- (</> "ekg-assets") <$> getDataDir -- (ekgStore, ekgMid) <- newEkgStore api
pure $ ekgMid $ serveWithContext apiWithEkg cfg -- ekgDir <- (</> "ekg-assets") <$> getDataDir
(ekgServer ekgDir ekgStore :<|> serv) -- pure $ ekgMid $ serveWithContext apiWithEkg cfg
-- (ekgServer ekgDir ekgStore :<|> serv)
where where
cfg :: Servant.Context AuthContext cfg :: Servant.Context AuthContext
cfg = env ^. settings . jwtSettings cfg = env ^. settings . jwtSettings
......
...@@ -21,6 +21,7 @@ module Gargantext.API.Routes ...@@ -21,6 +21,7 @@ module Gargantext.API.Routes
where where
import Control.Lens (view) import Control.Lens (view)
import Data.List qualified as L
import Data.Validity import Data.Validity
import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI, withAccess, withPolicyT) import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI, withAccess, withPolicyT)
import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..)) import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
...@@ -46,6 +47,7 @@ import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport ...@@ -46,6 +47,7 @@ import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport
import Gargantext.API.Node.ShareURL qualified as ShareURL import Gargantext.API.Node.ShareURL qualified as ShareURL
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Public qualified as Public import Gargantext.API.Public qualified as Public
import Gargantext.API.WebSockets qualified as WebSockets
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Viz.Graph.API import Gargantext.Core.Viz.Graph.API
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
...@@ -63,7 +65,6 @@ import Servant.Server.Internal.Delayed ...@@ -63,7 +65,6 @@ import Servant.Server.Internal.Delayed
import Servant.Server.Internal.DelayedIO import Servant.Server.Internal.DelayedIO
import Servant.Swagger import Servant.Swagger
import Servant.Swagger.UI import Servant.Swagger.UI
import qualified Data.List as L
data WithCustomErrorScheme a data WithCustomErrorScheme a
...@@ -238,7 +239,7 @@ type GargPrivateAPI' = ...@@ -238,7 +239,7 @@ type GargPrivateAPI' =
-- :<|> "auth" :> Capture "node_id" Int :> NodeAPI -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
--------------------------------------------------------------------- ---------------------------------------------------------------------
type API = WithCustomErrorScheme (SwaggerAPI :<|> GargAPI :<|> GraphQL.API :<|> FrontEndAPI) type API = WithCustomErrorScheme (WebSockets.API :<|> SwaggerAPI :<|> GargAPI :<|> GraphQL.API :<|> FrontEndAPI)
-- | API for serving @swagger.json@ -- | API for serving @swagger.json@
type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json" type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
......
...@@ -30,6 +30,7 @@ import Gargantext.API.Public qualified as Public ...@@ -30,6 +30,7 @@ import Gargantext.API.Public qualified as Public
import Gargantext.API.Routes (API, GargVersion, GargAPI) import Gargantext.API.Routes (API, GargVersion, GargAPI)
import Gargantext.API.Swagger (swaggerDoc) import Gargantext.API.Swagger (swaggerDoc)
import Gargantext.API.ThrowAll (serverPrivateGargAPI) import Gargantext.API.ThrowAll (serverPrivateGargAPI)
import Gargantext.API.WebSockets qualified as WebSockets
import Gargantext.Database.Prelude (hasConfig) import Gargantext.Database.Prelude (hasConfig)
import Gargantext.Prelude hiding (Handler, catch) import Gargantext.Prelude hiding (Handler, catch)
import Gargantext.Prelude.Config (gc_url_backend_api) import Gargantext.Prelude.Config (gc_url_backend_api)
...@@ -57,7 +58,9 @@ serverGargAPI baseUrl -- orchestrator ...@@ -57,7 +58,9 @@ serverGargAPI baseUrl -- orchestrator
server :: Env -> IO (Server API) server :: Env -> IO (Server API)
server env = do server env = do
-- orchestrator <- scrapyOrchestrator env -- orchestrator <- scrapyOrchestrator env
pure $ \errScheme -> swaggerSchemaUIServer swaggerDoc pure $ \errScheme ->
WebSockets.server
:<|> swaggerSchemaUIServer swaggerDoc
:<|> hoistServerWithContext :<|> hoistServerWithContext
(Proxy :: Proxy GargAPI) (Proxy :: Proxy GargAPI)
(Proxy :: Proxy AuthContext) (Proxy :: Proxy AuthContext)
......
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