Skip to content

Commit

Permalink
tests: make sequential test groups still allow running select tests
Browse files Browse the repository at this point in the history
This slows the tests by 20s on my machine but is probably worth it
for iteration speed, because it lets run individual tests (or groups)
at our whim.

See UnkindPartition/tasty#414 for background.

Change-Id: I4bd7f0ba24b29c4ce9bf18ea2842f57337c2dfa3
  • Loading branch information
edmundnoble committed Apr 30, 2024
1 parent afa4548 commit 3c97c7a
Show file tree
Hide file tree
Showing 9 changed files with 26 additions and 11 deletions.
6 changes: 4 additions & 2 deletions test/Chainweb/Test/Pact/GrandHash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,13 +37,15 @@ import Data.Vector qualified as Vector
import Data.Word (Word8, Word32, Word64)
import Streaming.Prelude qualified as S
import Test.QuickCheck (Property, Arbitrary, Gen, Positive(..), (===), arbitrary, elements)
import Test.Tasty (TestTree, DependencyType(..), sequentialTestGroup)
import Test.Tasty (TestTree)
import Test.Tasty.HUnit (Assertion, testCase, (@?=))
import Test.Tasty.QuickCheck (testProperty)

import Chainweb.Test.Utils

tests :: TestTree
tests =
sequentialTestGroup "Chainweb.Test.Pact.GrandHash" AllSucceed
independentSequentialTestGroup "Chainweb.Test.Pact.GrandHash"
[ testCase "PactRow hash input roundtrip - habibti ascii" (testPactRow habibtiAscii)
, testCase "PactRow hash input roundtrip - habibti utf8" (testPactRow habibtiUtf8)
, testProperty "PactRow hash input roundtrip - arbitrary utf8" propPactRowHashInputRoundtrip
Expand Down
3 changes: 1 addition & 2 deletions test/Chainweb/Test/Pact/ModuleCacheOnRestart.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,10 +79,9 @@ tests rdb =
withResource' newEmptyMVar $ \rewindDataM ->
withResource' (mkTestBlockDb testVer rdb) $ \bdbio ->
withResourceT withTempSQLiteResource $ \ioSqlEnv ->
sequentialTestGroup "Chainweb.Test.Pact.ModuleCacheOnRestart" AllSucceed
independentSequentialTestGroup "Chainweb.Test.Pact.ModuleCacheOnRestart"
[ testCaseSteps "testInitial" $ withPact' bdbio ioSqlEnv iom testInitial
, testCaseSteps "testRestart1" $ withPact' bdbio ioSqlEnv iom testRestart
-- wow, Tasty thinks there's a "loop" if the following test is called "testCoinbase"!!
, testCaseSteps "testDoUpgrades" $ withPact' bdbio ioSqlEnv iom (testCoinbase bdbio)
, testCaseSteps "testRestart2" $ withPact' bdbio ioSqlEnv iom testRestart
, testCaseSteps "testV3" $ withPact' bdbio ioSqlEnv iom (testV3 bdbio rewindDataM)
Expand Down
3 changes: 2 additions & 1 deletion test/Chainweb/Test/Pact/PactReplay.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ import Chainweb.BlockHeader
import Chainweb.BlockHeaderDB.Internal (unsafeInsertBlockHeaderDb)
import Chainweb.Graph
import Chainweb.Test.Cut.TestBlockDb
import Chainweb.Test.Utils
import Chainweb.Miner.Pact
import Chainweb.Pact.Backend.Types
import Chainweb.Pact.Service.BlockValidation
Expand Down Expand Up @@ -64,7 +65,7 @@ tests rdb =
let mp = snd <$> dmp
mpio = fst <$> dmp
in
sequentialTestGroup label AllSucceed
independentSequentialTestGroup label
[ withPactTestBlockDb testVer cid rdb mp (forkLimit $ RewindLimit 100_000)
(testCase "initial-playthrough" . firstPlayThrough mpio genblock)
, withPactTestBlockDb testVer cid rdb mp (forkLimit $ RewindLimit 100_000)
Expand Down
2 changes: 1 addition & 1 deletion test/Chainweb/Test/Pact/PactSingleChainTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -247,7 +247,7 @@ rosettaFailsWithoutFullHistory rdb =
withTemporaryDir $ \iodir ->
withSqliteDb cid iodir $ \sqlEnvIO ->
withDelegateMempool $ \dm ->
sequentialTestGroup "rosettaFailsWithoutFullHistory" AllSucceed
independentSequentialTestGroup "rosettaFailsWithoutFullHistory"
[
-- Run some blocks and then compact
withPactTestBlockDb' testVersion cid rdb sqlEnvIO mempty testPactServiceConfig $ \reqIO ->
Expand Down
2 changes: 1 addition & 1 deletion test/Chainweb/Test/Pact/RemotePactTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@ tests rdb = testGroup "Chainweb.Test.Pact.RemotePactTest"
let cenv = _getServiceClientEnv <$> net
iot = toTxCreationTime @Integer <$> getCurrentTimeIntegral

in sequentialTestGroup "remote pact tests" AllFinish
in independentSequentialTestGroup "remote pact tests"
[ withResourceT (liftIO $ join $ withRequestKeys <$> iot <*> cenv) $ \reqkeys -> golden "remote-golden" $
join $ responseGolden <$> cenv <*> reqkeys
, testCaseSteps "remote spv" $ \step ->
Expand Down
2 changes: 1 addition & 1 deletion test/Chainweb/Test/Rosetta/RestAPI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -118,7 +118,7 @@ tests rdb = testGroup "Chainweb.Test.Rosetta.RestAPI" go
go = return $
withResourceT (withNodeDbDirs rdb nodes) $ \dbdirs ->
withResourceT (withNodesAtLatestBehavior v (configRosetta .~ True) =<< liftIO dbdirs) $ \envIo ->
withResource' getCurrentTimeIntegral $ \tio -> sequentialTestGroup "Rosetta Api tests" AllFinish $
withResource' getCurrentTimeIntegral $ \tio -> independentSequentialTestGroup "Rosetta Api tests" $
tgroup tio $ _getServiceClientEnv <$> envIo

-- Not supported:
Expand Down
12 changes: 12 additions & 0 deletions test/Chainweb/Test/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ module Chainweb.Test.Utils
readFile'
, withResource'
, withResourceT
, independentSequentialTestGroup

-- * Test RocksDb
, testRocksDb
Expand Down Expand Up @@ -1144,3 +1145,14 @@ testRetryPolicy = stepped <> limitRetries 150
1 -> Just 50_000
2 -> Just 100_000
_ -> Just 500_000

independentSequentialTestGroup :: TestName -> [TestTree] -> TestTree
independentSequentialTestGroup tn tts =
withResource'
(newMVar ())
$ \mvarIO ->
testGroup tn $ tts <&> \tt ->
withResource
(mvarIO >>= takeMVar)
(\_ -> mvarIO >>= flip putMVar ())
$ \_ -> tt
4 changes: 2 additions & 2 deletions test/ChainwebTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ import qualified Chainweb.Test.Sync.WebBlockHeaderStore (properties)
import qualified Chainweb.Test.TreeDB (properties)
import qualified Chainweb.Test.TreeDB.RemoteDB
import Chainweb.Test.Utils
(toyChainId, withToyDB)
(independentSequentialTestGroup, toyChainId, withToyDB)
import qualified Chainweb.Test.Version (tests)
import qualified Chainweb.Test.Chainweb.Utils.Paging (properties)
import Chainweb.Version.Development
Expand Down Expand Up @@ -118,7 +118,7 @@ pactTestSuite rdb = testGroup "Chainweb-Pact Tests"
]

nodeTestSuite :: RocksDb -> TestTree
nodeTestSuite rdb = sequentialTestGroup "Tests starting nodes" AllFinish
nodeTestSuite rdb = independentSequentialTestGroup "Tests starting nodes"
[ Chainweb.Test.Rosetta.RestAPI.tests rdb
, Chainweb.Test.Pact.RemotePactTest.tests rdb
]
Expand Down
3 changes: 2 additions & 1 deletion test/SlowTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module SlowTests ( main ) where
import Chainweb.Graph
import Chainweb.Storage.Table.RocksDB
import Chainweb.Test.TestVersions
import Chainweb.Test.Utils
import System.IO.Temp
import System.LogLevel
import Test.Tasty
Expand All @@ -31,7 +32,7 @@ loglevel = Warn

-- note that because these tests run in parallel they must all use distinct rocksdb and sqlite dirs.
suite :: TestTree
suite = sequentialTestGroup "ChainwebSlowTests" AllFinish
suite = independentSequentialTestGroup "ChainwebSlowTests"
[ testCaseSteps "compact-resume" $ \step ->
withTempRocksDb "compact-resume-test-rocks" $ \rdb ->
withSystemTempDirectory "compact-resume-test-pact" $ \pactDbDir -> do
Expand Down

0 comments on commit 3c97c7a

Please sign in to comment.