{-| Module : Test.API.Worker Description : Basic tests for the async worker Copyright : (c) CNRS, 2017-Present License : AGPL + CECILL v3 Maintainer : team@gargantext.org Stability : experimental Portability : POSIX -} {-# OPTIONS_GHC -Wno-orphans #-} {-# LANGUAGE ScopedTypeVariables #-} module Test.API.Worker ( tests ) where import Control.Concurrent (threadDelay) import Control.Concurrent.Async (withAsync) import Control.Concurrent.STM.TChan import Control.Monad.STM (atomically) import Data.Aeson qualified as Aeson import Data.Maybe (isJust) import Gargantext.Core.Notifications.Dispatcher.Types qualified as DT import Gargantext.Core.Worker.Jobs (sendJobWithCfg) import Gargantext.Core.Worker.Jobs.Types (Job(Ping)) import Network.WebSockets qualified as WS import Prelude import System.Timeout qualified as Timeout import Test.API.Setup (SpecContext(..), withTestDBAndPort) import Test.Database.Types (test_config) import Test.Hspec import Test.Instances () import Test.Utils.Notifications tests :: Spec tests = sequential $ aroundAll withTestDBAndPort $ do describe "Worker" $ do it "simple Ping job works" $ \(SpecContext testEnv port _app _) -> do let cfg = test_config testEnv let topic = DT.Ping tchan <- newTChanIO :: IO (TChan (Maybe DT.Notification)) -- setup a websocket connection let wsConnect = withWSConnection ("127.0.0.1", port) $ \conn -> do WS.sendTextData conn $ Aeson.encode (DT.WSSubscribe topic) d <- WS.receiveData conn let dec = Aeson.decode d :: Maybe DT.Notification atomically $ writeTChan tchan dec -- wait a bit to settle threadDelay (100 * millisecond) withAsync wsConnect $ \_a -> do -- wait a bit to connect threadDelay (500 * millisecond) _ <- sendJobWithCfg cfg Ping mTimeout <- Timeout.timeout (5 * 1_000_000) $ do md <- atomically $ readTChan tchan md `shouldBe` Just DT.NPing mTimeout `shouldSatisfy` isJust