[tests] some fixes to invoking dispatcher and central exchange

parent 99f21ab0
Pipeline #6255 canceled with stages
......@@ -25,7 +25,6 @@ import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node (getOrMkList)
import Gargantext.Database.Query.Tree.Root (MkCorpusUser(..))
import Gargantext.Prelude (forkIO)
import Gargantext.Prelude.Config
import Gargantext.Prelude.Mail qualified as Mail
import Gargantext.Prelude.NLP qualified as NLP
......@@ -69,8 +68,8 @@ newTestEnv testEnv logger port = do
!config_mail <- Mail.readConfig file
!nlp_env <- nlpServerMap <$> NLP.readConfig file
!central_exchange <- forkIO CE.gServer
!dispatcher <- D.dispatcher
-- !central_exchange <- forkIO CE.gServer
-- !dispatcher <- D.dispatcher
pure $ Env
{ _env_settings = settings'
......@@ -84,8 +83,10 @@ newTestEnv testEnv logger port = do
, _env_config = config_env
, _env_mail = config_mail
, _env_nlp = nlp_env
, _env_central_exchange = central_exchange
, _env_dispatcher = dispatcher
, _env_central_exchange = Prelude.error "central exchange not needed, but forced somewhere (check StrictData)"
, _env_dispatcher = Prelude.error "dispatcher not needed, but forced somewhere (check StrictData)"
-- , _env_central_exchange = central_exchange
-- , _env_dispatcher = dispatcher
}
withGargApp :: Application -> (Warp.Port -> IO ()) -> IO ()
......
......@@ -4,8 +4,12 @@ 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
import Gargantext.Core.AsyncUpdates.Dispatcher qualified as D
import Gargantext.Core.AsyncUpdates.Dispatcher.Types qualified as DT
import Shelly hiding (FilePath)
import System.IO
import System.Process
......@@ -36,6 +40,17 @@ startCoreNLPServer = do
stopCoreNLPServer :: ProcessHandle -> IO ()
stopCoreNLPServer = interruptProcessGroupOf
startNotifications = do
central_exchange <- forkIO CE.gServer
dispatcher <- D.dispatcher
pure (central_exchange, dispatcher)
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,
-- unlike 'tasty', 'Hspec' has explicit control over parallelism,
-- and it's important that DB tests are run according to a very
......@@ -50,7 +65,8 @@ stopCoreNLPServer = interruptProcessGroupOf
main :: IO ()
main = do
hSetBuffering stdout NoBuffering
bracket startCoreNLPServer stopCoreNLPServer $ \_ -> hspec $ do
API.tests
DB.tests
DB.nodeStoryTests
bracket startNotifications stopNotifications $ \_ -> do
bracket startCoreNLPServer stopCoreNLPServer $ \_ -> hspec $ do
API.tests
DB.tests
DB.nodeStoryTests
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