Commit 65053486 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

ws: abstract with pattern in withNotifications

This commit refactors the common pattern `bracket init deinit use` in
`withNotifications` in `drivers.hspec.Main`, so that `withNotifications`
in atomic and the user doesn't incur in the pattern of using the init
and deinit functions independently from the `bracket`.

To be faithful about what I preach, we should do the same for
`startCoreNLPServer` and `stopCoreNLPServer`.
parent c5336b22
......@@ -4,7 +4,6 @@ module Main where
import Gargantext.Prelude hiding (isInfixOf)
import Control.Concurrent (forkIO, killThread)
import Control.Monad
import Data.Text (isInfixOf)
import Gargantext.Core.AsyncUpdates.CentralExchange qualified as CE
......@@ -41,16 +40,17 @@ startCoreNLPServer = do
stopCoreNLPServer :: ProcessHandle -> IO ()
stopCoreNLPServer = interruptProcessGroupOf
startNotifications :: IO (ThreadId, DT.Dispatcher)
startNotifications = do
withNotifications :: ((ThreadId, DT.Dispatcher) -> IO a) -> IO a
withNotifications = bracket startNotifications stopNotifications
where
startNotifications :: IO (ThreadId, DT.Dispatcher)
startNotifications = do
central_exchange <- forkIO CE.gServer
dispatcher <- D.dispatcher
pure (central_exchange, dispatcher)
stopNotifications :: (ThreadId, DT.Dispatcher) -> IO ()
stopNotifications (central_exchange, dispatcher) = do
stopNotifications :: (ThreadId, DT.Dispatcher) -> IO ()
stopNotifications (central_exchange, dispatcher) = do
killThread central_exchange
killThread $ DT.d_ce_listener dispatcher
......@@ -70,7 +70,7 @@ main = do
hSetBuffering stdout NoBuffering
-- TODO Ideally remove start/stop notifications and use
-- Test/API/Setup to initialize this in env
bracket startNotifications stopNotifications $ \_ -> do
withNotifications $ \_ -> do
bracket startCoreNLPServer stopCoreNLPServer $ \_ -> hspec $ do
API.tests
ReverseProxy.tests
......
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