Skip to content

Commit bd996fd

Browse files
committed
wrong block
1 parent aca74cc commit bd996fd

File tree

3 files changed

+24
-4
lines changed
  • ouroboros-consensus-diffusion/app/conformance-test-runner
  • ouroboros-consensus/src/unstable-consensus-testlib/Test/Util

3 files changed

+24
-4
lines changed

ouroboros-consensus-diffusion/app/conformance-test-runner/Main.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,7 @@
1+
{-# LANGUAGE FlexibleInstances #-}
2+
{-# LANGUAGE MultiParamTypeClasses #-}
3+
{-# LANGUAGE TypeSynonymInstances #-}
4+
15
module Main (main) where
26

37
import qualified Data.Map.Merge.Lazy as M
@@ -30,6 +34,9 @@ import System.Environment (getArgs)
3034
import Test.Consensus.OrphanInstances ()
3135
import Test.Consensus.PointSchedule (PointSchedule (..))
3236
import Test.Consensus.PointSchedule.Peers (PeerId (..), Peers (Peers), getPeerIds)
37+
import Test.Util.TestBlock
38+
import Ouroboros.Consensus.Node.Serialisation
39+
import Ouroboros.Consensus.Block.Abstract
3340

3441
testPointSchedule :: PointSchedule blk
3542
testPointSchedule =
@@ -85,6 +92,8 @@ main = do
8592
zipMaps :: Ord k => Map k a -> Map k b -> Map k (a, b)
8693
zipMaps = M.merge M.dropMissing M.dropMissing $ M.zipWithMatched $ const (,)
8794

95+
instance SerialiseNodeToNode TestBlock (Header TestBlock)
96+
8897
runServer :: IO ()
8998
runServer = do
9099
let peerMap = buildPeerMap 6001 testPointSchedule

ouroboros-consensus-diffusion/app/conformance-test-runner/Server.hs

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@
77

88
module Server (run) where
99

10+
import Ouroboros.Consensus.Node.Serialisation
11+
import Ouroboros.Consensus.Node.ProtocolInfo (NumCoreNodes (..))
1012
import Test.Consensus.PeerSimulator.Resources (PeerResources)
1113
import Control.ResourceRegistry
1214
import Control.Tracer
@@ -35,6 +37,8 @@ import qualified Ouroboros.Network.Protocol.Handshake as Handshake
3537
import qualified Ouroboros.Network.Server.Simple as Server
3638
import qualified Ouroboros.Network.Snocket as Snocket
3739
import Ouroboros.Network.Socket (SomeResponderApplication (..), configureSocket)
40+
import Test.Util.TestBlock (TestBlock)
41+
import qualified Test.Util.TestBlock as TB
3842

3943
-- | Glue code for using just the bits from the Diffusion Layer that we need in
4044
-- this context.
@@ -68,7 +72,7 @@ run ::
6872
( SupportedNetworkProtocolVersion blk
6973
, SerialiseNodeToNodeConstraints blk
7074
, ConfigSupportsNode blk
71-
, blk ~ SimpleBlock SimpleMockCrypto SimplePraosRuleExt
75+
, blk ~ TestBlock
7276
) =>
7377
PeerResources IO blk ->
7478
-- | A TMVar for the chainsync channel that we will fill in once the node connects.
@@ -79,11 +83,11 @@ run ::
7983
IO Void
8084
run res csChanTMV bfChanTMV sockAddr = withRegistry \_registry ->
8185
serve sockAddr
82-
$ peerSimServer @_ @(SimpleBlock SimpleMockCrypto SimplePraosRuleExt)
86+
$ peerSimServer @_ @TestBlock
8387
res
8488
csChanTMV
8589
bfChanTMV
86-
SimpleCodecConfig
90+
TB.TestBlockCodecConfig
8791
encodeRemoteAddress
8892
decodeRemoteAddress
89-
$ getNetworkMagic @(SimpleBlock SimpleMockCrypto SimplePraosRuleExt) SimpleBlockConfig
93+
$ getNetworkMagic @TestBlock $ TB.TestBlockConfig $ NumCoreNodes 0

ouroboros-consensus/src/unstable-consensus-testlib/Test/Util/TestBlock.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -226,6 +226,13 @@ data Validity = Valid | Invalid
226226
deriving stock (Show, Eq, Ord, Enum, Bounded, Generic)
227227
deriving anyclass (Serialise, NoThunks, ToExpr)
228228

229+
230+
instance SupportedNetworkProtocolVersion (TestBlockWith ptype) where
231+
supportedNodeToNodeVersions _ = foldMap (flip Map.singleton ()) [minBound .. maxBound]
232+
supportedNodeToClientVersions _ = foldMap (flip Map.singleton ()) [minBound .. maxBound]
233+
234+
latestReleasedNodeVersion = latestReleasedNodeVersionDefault
235+
229236
-- | Test block parametrized on the payload type
230237
--
231238
-- For blocks without payload see the 'TestBlock' type alias.

0 commit comments

Comments
 (0)