Skip to content

Commit

Permalink
Define adjustQuickCheckTestsAccordingToEnv
Browse files Browse the repository at this point in the history
This function allows to adjust the number of tests to run based on the
given `QuickCheckTestsPerEnv` option.

The use of this function is demonstrated in the `AllegraMary` ThreadNet
tests, and in the `ChainDB` state-machine tests, where we remove the use
of `withMaxSuccess` in favour of this new function.
  • Loading branch information
dnadales committed Aug 10, 2022
1 parent 63f58bc commit fb56c18
Show file tree
Hide file tree
Showing 3 changed files with 42 additions and 28 deletions.
38 changes: 14 additions & 24 deletions ouroboros-consensus-cardano-test/test/Test/ThreadNet/AllegraMary.hs
Expand Up @@ -69,8 +69,9 @@ import qualified Test.Util.BoolProps as BoolProps
import Test.Util.HardFork.Future (EraSize (..), Future (..))
import Test.Util.Orphans.Arbitrary ()
import Test.Util.Slots (NumSlots (..))
import Test.Util.TestMode (IohkTestMode (..), askIohkTestMode,
resetQuickCheckTests)
import Test.Util.TestMode
(QuickCheckTestsPerEnv (QuickCheckTestsPerEnv, ci, dev, nightly),
adjustQuickCheckTestsAccordingToEnv)

import Test.Consensus.Shelley.MockCrypto (MockCrypto)
import qualified Test.ThreadNet.Infra.Shelley as Shelley
Expand Down Expand Up @@ -153,29 +154,18 @@ instance Arbitrary TestSetup where

-- TODO shrink

-- | Run relatively fewer tests
--
-- These tests are slow, so we settle for running fewer of them in this test
-- suite since it is invoked frequently (eg CI for each push).
oneTenthTestCount :: QuickCheckTests -> QuickCheckTests
oneTenthTestCount (QuickCheckTests n) = QuickCheckTests $
if 0 == n then 0 else
max 1 $ n `div` 10

tests :: TestTree
tests = testGroup "AllegraMary ThreadNet" $
[ let name = "simple convergence" in
askIohkTestMode $ flip adjustTestMode $
testProperty name $ \setup ->
prop_simple_allegraMary_convergence setup
]

where
adjustTestMode :: IohkTestMode -> TestTree -> TestTree
adjustTestMode = \case
Nightly -> resetQuickCheckTests id
CI -> resetQuickCheckTests oneTenthTestCount
Dev -> resetQuickCheckTests oneTenthTestCount
tests = adjustQuickCheckTestsAccordingToEnv nrTests
$ testGroup "AllegraMary ThreadNet" $
[ testProperty "simple convergence" $ \setup ->
prop_simple_allegraMary_convergence setup
]
where
nrTests = QuickCheckTestsPerEnv
{ nightly = 1000
, ci = 100
, dev = 10
}

prop_simple_allegraMary_convergence :: TestSetup -> Property
prop_simple_allegraMary_convergence TestSetup
Expand Down
16 changes: 16 additions & 0 deletions ouroboros-consensus-test/src/Test/Util/TestMode.hs
Expand Up @@ -2,6 +2,8 @@
-- | A @tasty@ command-line option for enabling nightly tests
module Test.Util.TestMode (
IohkTestMode (..)
, QuickCheckTestsPerEnv (QuickCheckTestsPerEnv, ci, dev, nightly)
, adjustQuickCheckTestsAccordingToEnv
, askIohkTestMode
, defaultMainWithIohkTestMode
, iohkTestModeIngredient
Expand Down Expand Up @@ -47,6 +49,20 @@ defaultTestEnv testTree = \case
CI -> adjustOption (const (QuickCheckTests 10000)) testTree
Dev -> testTree

-- | QuickCheck tests to run per-environment.
data QuickCheckTestsPerEnv = QuickCheckTestsPerEnv
{ nightly :: Int
, ci :: Int
, dev :: Int
}

adjustQuickCheckTestsAccordingToEnv :: QuickCheckTestsPerEnv -> TestTree -> TestTree
adjustQuickCheckTestsAccordingToEnv nrTests testTree = askOption $
\case
Nightly -> const (QuickCheckTests (nightly nrTests)) `adjustOption` testTree
CI -> const (QuickCheckTests (ci nrTests)) `adjustOption` testTree
Dev -> const (QuickCheckTests (dev nrTests)) `adjustOption` testTree

-- | Reset quickcheck tests
resetQuickCheckTests :: (QuickCheckTests -> QuickCheckTests) -> TestTree -> TestTree
resetQuickCheckTests f = adjustOption $ const (f (QuickCheckTests 100))
Expand Down
Expand Up @@ -115,6 +115,9 @@ import Test.Util.Orphans.ToExpr ()
import Test.Util.RefEnv (RefEnv)
import qualified Test.Util.RefEnv as RE
import Test.Util.SOP
import Test.Util.TestMode
(QuickCheckTestsPerEnv (QuickCheckTestsPerEnv, ci, dev, nightly),
adjustQuickCheckTestsAccordingToEnv)
import Test.Util.Tracer (recordingTracerIORef)
import Test.Util.WithEq

Expand Down Expand Up @@ -1460,7 +1463,7 @@ smUnused maxClockSkew chunkInfo =
maxClockSkew

prop_sequential :: MaxClockSkew -> SmallChunkInfo -> Property
prop_sequential maxClockSkew (SmallChunkInfo chunkInfo) = withMaxSuccess 100000 $
prop_sequential maxClockSkew (SmallChunkInfo chunkInfo) =
forAllCommands (smUnused maxClockSkew chunkInfo) Nothing $ \cmds ->
QC.monadicIO $ do
let
Expand Down Expand Up @@ -1663,6 +1666,11 @@ mkArgs cfg (MaxClockSkew maxClockSkew) chunkInfo initLedger tracer registry varC
}

tests :: TestTree
tests = testGroup "ChainDB q-s-m"
[ testProperty "sequential" prop_sequential
]
tests = adjustQuickCheckTestsAccordingToEnv nrTests
$ testGroup "ChainDB q-s-m" [ testProperty "sequential" $ prop_sequential ]
where
nrTests = QuickCheckTestsPerEnv
{ nightly = 100000
, ci = 10000
, dev = 100
}

0 comments on commit fb56c18

Please sign in to comment.