Skip to content

Commit

Permalink
Try #2194:
Browse files Browse the repository at this point in the history
  • Loading branch information
iohk-bors[bot] authored Sep 30, 2020
2 parents 28d90fb + 766200b commit 4bf6f30
Show file tree
Hide file tree
Showing 2 changed files with 63 additions and 23 deletions.
56 changes: 43 additions & 13 deletions lib/test-utils/src/Test/Hspec/Extra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}

-- |
-- Copyright: © 2018-2020 IOHK
Expand All @@ -13,16 +14,21 @@
module Test.Hspec.Extra
( aroundAll
, it
, itWithCustomTimeout
) where

import Prelude

import Control.Concurrent
( threadDelay )
import Control.Concurrent.Async
( async, race, wait )
( AsyncCancelled, async, race, race_, wait )
import Control.Concurrent.MVar
( MVar, newEmptyMVar, putMVar, takeMVar )
import Control.Exception
( SomeException, throwIO, try )
( SomeException, fromException, throwIO, try )
import Data.Maybe
( isJust )
import Test.Hspec
( ActionWith
, HasCallStack
Expand All @@ -31,6 +37,7 @@ import Test.Hspec
, afterAll
, beforeAll
, beforeWith
, expectationFailure
, specify
)

Expand Down Expand Up @@ -103,18 +110,41 @@ aroundAll acquire =

-- | A drop-in replacement for 'it' that'll automatically retry a scenario once
-- if it fails, to cope with potentially flaky tests.
--
-- It also has a timeout of 10 minutes.
it :: HasCallStack => String -> ActionWith ctx -> SpecWith ctx
it title action = specify title $ \ctx -> do
res1 <- try $ action ctx
case res1 of
Right r1 -> return r1
Left (e1 :: SomeException) -> do
res2 <- try $ action ctx
case res2 of
-- If the second try fails, return the first error. The
-- second error might not be helpful.
Left (_e2 :: SomeException) -> throwIO e1
Right r2 -> return r2
it = itWithCustomTimeout (10*minute)
where
minute = 60*1000*1000

-- | Like @it@ but with a custom timeout, which makes it realistic to test.
itWithCustomTimeout :: HasCallStack => Int -> String -> ActionWith ctx -> SpecWith ctx
itWithCustomTimeout micro title action = specify title $ \ctx -> do
race_ timeout $ do
res1 <- try $ action ctx
case res1 of
Right r1 -> return r1
Left (e1 :: SomeException)
-- If we time out during the first attempt, then we /should/ time
-- out.
| isAsyncCancelled e1 -> throwIO e1
| otherwise -> do
res2 <- try $ action ctx
case res2 of
-- If the second try fails, return the first error. The
-- second error might not be helpful.
Left (e2 :: SomeException)
| isAsyncCancelled e2 -> throwIO e1
| otherwise -> throwIO e1
Right r2 -> return r2
where
isAsyncCancelled = isJust . fromException @AsyncCancelled
timeout = do
threadDelay micro
expectationFailure
$ "timed out in "
<> show (micro `div` 1000000)
<> " seconds"

-- | Some helper to help readability on the thread synchronization above.
await :: MVar () -> IO ()
Expand Down
30 changes: 20 additions & 10 deletions lib/test-utils/test/Test/Hspec/ExtraSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@ module Test.Hspec.ExtraSpec where

import Prelude

import Control.Concurrent
( threadDelay )
import Data.IORef
( IORef, newIORef, readIORef, writeIORef )
import Data.List
Expand All @@ -18,6 +20,7 @@ import Test.Hspec
, expectationFailure
, it
, shouldBe
, shouldContain
)
import Test.Hspec.Core.Runner
( defaultConfig, runSpec )
Expand Down Expand Up @@ -52,6 +55,14 @@ spec = do
let noRetry = expectationFailure "test can't be retried"
outcomes <- newIORef [failure, noRetry]
(dynamically outcomes) `shouldMatchHSpecIt` failure
it "can time out" $ do
let s = 1000*1000
let timeout = do
threadDelay (10 * s)
expectationFailure "should have timed out"
res <- run (Extra.itWithCustomTimeout $ 2 * s) timeout
res `shouldContain` "timed out in 2 seconds"

where
-- | lhs `shouldMatchHSpecIt` rhs asserts that the output of running
-- (Extra.it "" lhs) and (Hspec.it "" rhs) are equal. Modulo random seed-
Expand All @@ -62,17 +73,16 @@ spec = do
hspecRes <- run it hspecTest
extraRes `shouldBe` hspecRes

run
:: (String -> ActionWith () -> SpecWith ())
-> IO ()
-> IO String
run anyIt prop = fmap stripTime
$ capture_
$ flip runSpec defaultConfig
$ beforeAll (return ())
$ anyIt "<test spec>" (const prop)
where
run
:: (String -> ActionWith () -> SpecWith ())
-> IO ()
-> IO String
run anyIt prop = fmap stripTime
$ capture_
$ flip runSpec defaultConfig
$ beforeAll (return ())
$ anyIt "<test spec>" (const prop)

stripTime :: String -> String
stripTime = unlines
. filter (not . ("Finished in" `isPrefixOf`))
Expand Down

0 comments on commit 4bf6f30

Please sign in to comment.