Skip to content

Commit

Permalink
Set timeouts on the oura tests
Browse files Browse the repository at this point in the history
  • Loading branch information
Renegatto committed Sep 13, 2024
1 parent a1000c5 commit 193b357
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 18 deletions.
18 changes: 9 additions & 9 deletions test/OuraFilters.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,15 +76,15 @@ ouraFiltersSpec = Utils.killProcessesOnError do
let
tx = Mock.txToBS exampleTx
matchingTx = Mock.txToBS exampleMatchingTx
oura.send tx
-- _ <- oura.receive
oura.send matchingTx
Right outTxHash <-
extractOutputTxHash <$> oura.receive
Right inputTxHash <-
pure $ extractInputTxHash matchingTx
outTxHash `shouldBe` inputTxHash
oura.shutDown
Utils.withTimeout 3.0 do
oura.send tx
oura.send matchingTx
Right outTxHash <-
extractOutputTxHash <$> oura.receive
Right inputTxHash <-
pure $ extractInputTxHash matchingTx
outTxHash `shouldBe` inputTxHash
oura.shutDown
OuraFilters.Auction.spec

extractInputTxHash :: BS.ByteString -> Either String T.Text
Expand Down
21 changes: 12 additions & 9 deletions test/OuraFilters/Auction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,16 +9,17 @@ import Control.Arrow ((>>>))
import Control.Lens ((%~), (.~), (^.))
import Data.Aeson qualified as Aeson
import Data.Function ((&))
import Data.Functor ((<&>))
import Data.Functor (void, (<&>))
import Oura qualified
import OuraFilters.Mock qualified as Mock
import PlutusLedgerApi.V1 qualified
import PlutusLedgerApi.V1.Value qualified as V1.Value
import PlutusTx.AssocMap qualified as AssocMap
import System.Process (ProcessHandle)
import System.Timeout (timeout)
import Test.Hspec (describe, focus, it, shouldBe)
import Test.Hspec.Core.Spec (SpecM)
import Utils (SpotGarbage)
import Utils (SpotGarbage, withTimeout)
import Prelude

spec :: SpecM (SpotGarbage IO ProcessHandle) ()
Expand Down Expand Up @@ -47,13 +48,15 @@ spec =
Mock.hash .~ rightTxHash $
createTxMock params
unmatchingTx = Mock.txToBS $ Mock.mkTxEvent Mock.arbitraryTx
oura.send unmatchingTx
oura.send tx
Right txEvent <-
Aeson.eitherDecodeStrict @Mock.TxEvent
<$> oura.receive
(txEvent ^. Mock.parsed_tx . Mock.hash) `shouldBe` rightTxHash
oura.shutDown
withTimeout 3.0 do
oura.send unmatchingTx
oura.send tx
-- 2 sec
Right txEvent <-
Aeson.eitherDecodeStrict @Mock.TxEvent
<$> oura.receive
(txEvent ^. Mock.parsed_tx . Mock.hash) `shouldBe` rightTxHash
oura.shutDown
it "Recognizes 'Start' transition" \spotGarbage -> do
fail @IO @() "Not implemented"
it "Recognizes 'MakeBid' transition" \spotGarbage -> do
Expand Down
7 changes: 7 additions & 0 deletions test/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,15 +45,22 @@ import Cardano.Extras
import Data.Spine (HasSpine (..))

import Control.Exception (bracket)
import Control.Monad ((<=<))
import Data.Aeson.Types qualified as Aeson
import Data.Foldable (traverse_)
import Data.IORef qualified as IORef
import System.Directory (removeFile)
import System.IO (hClose, openTempFile)
import System.Process qualified as Process
import System.Timeout (timeout)
import Test.Hspec qualified as Hspec
import TestNFT

withTimeout :: (Hspec.HasCallStack) => Float -> IO a -> IO a
withTimeout sec =
maybe (error "Failed by timeout") pure
<=< timeout (round $ sec * 10 ** 6)

resultToEither :: Aeson.Result a -> Either String a
resultToEither (Aeson.Success a) = Right a
resultToEither (Aeson.Error err) = Left err
Expand Down

0 comments on commit 193b357

Please sign in to comment.