Skip to content

Commit 0778f2d

Browse files
committed
wrong block
1 parent 8b64183 commit 0778f2d

File tree

4 files changed

+25
-5
lines changed

4 files changed

+25
-5
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
@@ -29,6 +33,9 @@ import Server (run)
2933
import System.Environment (getArgs)
3034
import Test.Consensus.PointSchedule (PointSchedule (..))
3135
import Test.Consensus.PointSchedule.Peers (PeerId (..), Peers (Peers), getPeerIds)
36+
import Test.Util.TestBlock
37+
import Ouroboros.Consensus.Node.Serialisation
38+
import Ouroboros.Consensus.Block.Abstract
3239

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

94+
instance SerialiseNodeToNode TestBlock (Header TestBlock)
95+
8796
runServer :: IO ()
8897
runServer = do
8998
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
@@ -34,6 +36,8 @@ import qualified Ouroboros.Network.Protocol.Handshake as Handshake
3436
import qualified Ouroboros.Network.Server.Simple as Server
3537
import qualified Ouroboros.Network.Snocket as Snocket
3638
import Ouroboros.Network.Socket (SomeResponderApplication (..), configureSocket)
39+
import Test.Util.TestBlock (TestBlock)
40+
import qualified Test.Util.TestBlock as TB
3741

3842
-- | Glue code for using just the bits from the Diffusion Layer that we need in
3943
-- this context.
@@ -67,7 +71,7 @@ run ::
6771
( SupportedNetworkProtocolVersion blk
6872
, SerialiseNodeToNodeConstraints blk
6973
, ConfigSupportsNode blk
70-
, blk ~ SimpleBlock SimpleMockCrypto SimplePraosRuleExt
74+
, blk ~ TestBlock
7175
) =>
7276
PeerResources IO blk ->
7377
-- | A TMVar for the chainsync channel that we will fill in once the node connects.
@@ -78,11 +82,11 @@ run ::
7882
IO Void
7983
run res csChanTMV bfChanTMV sockAddr = withRegistry \_registry ->
8084
serve sockAddr
81-
$ peerSimServer @_ @(SimpleBlock SimpleMockCrypto SimplePraosRuleExt)
85+
$ peerSimServer @_ @TestBlock
8286
res
8387
csChanTMV
8488
bfChanTMV
85-
SimpleCodecConfig
89+
TB.TestBlockCodecConfig
8690
encodeRemoteAddress
8791
decodeRemoteAddress
88-
$ getNetworkMagic @(SimpleBlock SimpleMockCrypto SimplePraosRuleExt) SimpleBlockConfig
92+
$ getNetworkMagic @TestBlock $ TB.TestBlockConfig $ NumCoreNodes 0

ouroboros-consensus-diffusion/ouroboros-consensus-diffusion.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -343,7 +343,7 @@ executable conformance-test-runner
343343
containers,
344344
optparse-applicative,
345345
ouroboros-network:{ouroboros-network, orphan-instances},
346-
ouroboros-consensus:{ouroboros-consensus, unstable-mock-block},
346+
ouroboros-consensus:{ouroboros-consensus, unstable-mock-block, unstable-consensus-testlib},
347347
ouroboros-network-api,
348348
unstable-consensus-conformance-testlib,
349349
aeson,

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)