Commit 45037f2d authored by Alfredo Di Napoli's avatar Alfredo Di Napoli Committed by Alfredo Di Napoli

fix(tests) Increase timeout in 'simple Ping job works' test

This commit extends the timeout around the `readTChan` in the ping-pong
test to 60 seconds, mostly to account for CI slowness and to rule-out
potential source of flakyness.

The calls to `threadDelay` have been removed, as they doesn't seem to
affect the overall stability of the test (at least locally) -- the
point of the exercise is trying to expose as much as possible potential
problems which might be masked by active waits.
parent da942cf9
......@@ -13,12 +13,11 @@ Portability : POSIX
{-# 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)
......@@ -43,7 +42,7 @@ 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
......@@ -53,19 +52,13 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
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
mTimeout <- Timeout.timeout (60 * 1_000_000) $ do
md <- atomically $ readTChan tchan
md `shouldBe` Just DT.NPing
mTimeout `shouldSatisfy` isJust
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