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 ...@@ -4,7 +4,6 @@ module Main where
import Gargantext.Prelude hiding (isInfixOf) import Gargantext.Prelude hiding (isInfixOf)
import Control.Concurrent (forkIO, killThread)
import Control.Monad import Control.Monad
import Data.Text (isInfixOf) import Data.Text (isInfixOf)
import Gargantext.Core.AsyncUpdates.CentralExchange qualified as CE import Gargantext.Core.AsyncUpdates.CentralExchange qualified as CE
...@@ -41,19 +40,20 @@ startCoreNLPServer = do ...@@ -41,19 +40,20 @@ startCoreNLPServer = do
stopCoreNLPServer :: ProcessHandle -> IO () stopCoreNLPServer :: ProcessHandle -> IO ()
stopCoreNLPServer = interruptProcessGroupOf stopCoreNLPServer = interruptProcessGroupOf
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)
startNotifications :: IO (ThreadId, DT.Dispatcher) stopNotifications :: (ThreadId, DT.Dispatcher) -> IO ()
startNotifications = do stopNotifications (central_exchange, dispatcher) = do
central_exchange <- forkIO CE.gServer killThread central_exchange
dispatcher <- D.dispatcher killThread $ DT.d_ce_listener dispatcher
pure (central_exchange, dispatcher)
stopNotifications :: (ThreadId, DT.Dispatcher) -> IO ()
stopNotifications (central_exchange, dispatcher) = do
killThread central_exchange
killThread $ DT.d_ce_listener dispatcher
-- It's especially important to use Hspec for DB tests, because, -- It's especially important to use Hspec for DB tests, because,
-- unlike 'tasty', 'Hspec' has explicit control over parallelism, -- unlike 'tasty', 'Hspec' has explicit control over parallelism,
-- and it's important that DB tests are run according to a very -- and it's important that DB tests are run according to a very
...@@ -70,7 +70,7 @@ main = do ...@@ -70,7 +70,7 @@ main = do
hSetBuffering stdout NoBuffering hSetBuffering stdout NoBuffering
-- TODO Ideally remove start/stop notifications and use -- TODO Ideally remove start/stop notifications and use
-- Test/API/Setup to initialize this in env -- Test/API/Setup to initialize this in env
bracket startNotifications stopNotifications $ \_ -> do withNotifications $ \_ -> do
bracket startCoreNLPServer stopCoreNLPServer $ \_ -> hspec $ do bracket startCoreNLPServer stopCoreNLPServer $ \_ -> hspec $ do
API.tests API.tests
ReverseProxy.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