Skip to content

Commit a01908c

Browse files
committed
MockChainSel: switch to weighted chain selection
1 parent 7d02cc5 commit a01908c

File tree

4 files changed

+38
-22
lines changed
  • ouroboros-consensus
    • src
    • test
      • consensus-test/Test/Consensus/MiniProtocol/LocalStateQuery
      • storage-test/Test/Ouroboros/Storage/ChainDB

4 files changed

+38
-22
lines changed

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Protocol/MockChainSel.hs

Lines changed: 12 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -9,9 +9,9 @@ module Ouroboros.Consensus.Protocol.MockChainSel
99
import Data.List (sortOn)
1010
import Data.Maybe (listToMaybe, mapMaybe)
1111
import Data.Ord (Down (..))
12+
import Ouroboros.Consensus.Peras.SelectView (WeightedSelectView (..), WithEmptyFragment (..))
1213
import Ouroboros.Consensus.Protocol.Abstract
1314
import Ouroboros.Network.Mock.Chain (Chain)
14-
import qualified Ouroboros.Network.Mock.Chain as Chain
1515

1616
{-------------------------------------------------------------------------------
1717
Chain selection
@@ -33,8 +33,9 @@ selectChain ::
3333
forall proxy p hdr l.
3434
ConsensusProtocol p =>
3535
proxy p ->
36-
ChainOrderConfig (SelectView p) ->
37-
(hdr -> SelectView p) ->
36+
ChainOrderConfig (WeightedSelectView p) ->
37+
-- | Compute the 'WeightedSelectView' of a chain.
38+
(Chain hdr -> WithEmptyFragment (WeightedSelectView p)) ->
3839
-- | Our chain
3940
Chain hdr ->
4041
-- | Upstream chains
@@ -51,24 +52,19 @@ selectChain _ cfg view ours =
5152
-- extract the 'SelectView' of the tip of the candidate.
5253
selectPreferredCandidate ::
5354
(Chain hdr, l) ->
54-
Maybe (SelectView p, (Chain hdr, l))
55-
selectPreferredCandidate x@(cand, _) =
56-
case (Chain.head ours, Chain.head cand) of
57-
(Nothing, Just candTip) ->
58-
Just (view candTip, x)
59-
(Just ourTip, Just candTip)
60-
| let candView = view candTip
61-
, preferCandidate cfg (view ourTip) candView ->
62-
Just (candView, x)
63-
_otherwise ->
64-
Nothing
55+
Maybe (WithEmptyFragment (WeightedSelectView p), (Chain hdr, l))
56+
selectPreferredCandidate x@(cand, _)
57+
| let candView = view cand
58+
, preferCandidate cfg (view ours) candView =
59+
Just (candView, x)
60+
| otherwise = Nothing
6561

6662
-- | Chain selection on unvalidated chains
6763
selectUnvalidatedChain ::
6864
ConsensusProtocol p =>
6965
proxy p ->
70-
ChainOrderConfig (SelectView p) ->
71-
(hdr -> SelectView p) ->
66+
ChainOrderConfig (WeightedSelectView p) ->
67+
(Chain hdr -> WithEmptyFragment (WeightedSelectView p)) ->
7268
Chain hdr ->
7369
[Chain hdr] ->
7470
Maybe (Chain hdr)

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

Lines changed: 11 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -139,6 +139,8 @@ import Ouroboros.Consensus.Ledger.Tables.Utils
139139
import Ouroboros.Consensus.Node.NetworkProtocolVersion
140140
import Ouroboros.Consensus.Node.ProtocolInfo
141141
import Ouroboros.Consensus.NodeId
142+
import Ouroboros.Consensus.Peras.SelectView (weightedSelectView)
143+
import Ouroboros.Consensus.Peras.Weight (PerasWeightSnapshot)
142144
import Ouroboros.Consensus.Protocol.Abstract
143145
import Ouroboros.Consensus.Protocol.BFT
144146
import Ouroboros.Consensus.Protocol.MockChainSel
@@ -859,15 +861,21 @@ treeToBlocks = Tree.flatten . blockTree
859861
treeToChains :: BlockTree -> [Chain TestBlock]
860862
treeToChains = map Chain.fromOldestFirst . allPaths . blockTree
861863

862-
treePreferredChain :: BlockTree -> Chain TestBlock
863-
treePreferredChain =
864+
treePreferredChain ::
865+
PerasWeightSnapshot TestBlock ->
866+
BlockTree ->
867+
Chain TestBlock
868+
treePreferredChain weights =
864869
fromMaybe Genesis
865870
. selectUnvalidatedChain
866871
(Proxy @(BlockProtocol TestBlock))
867872
(() :: ChainOrderConfig (SelectView (BlockProtocol TestBlock)))
868-
(\hdr -> SelectView (blockNo hdr) NoTiebreaker)
873+
(weightedSelectView bcfg weights . Chain.toAnchoredFragment . fmap getHeader)
869874
Genesis
870875
. treeToChains
876+
where
877+
-- inconsequential for this function
878+
bcfg = TestBlockConfig (NumCoreNodes 0)
871879

872880
instance Show BlockTree where
873881
show (BlockTree t) = Tree.drawTree (fmap show t)

ouroboros-consensus/test/consensus-test/Test/Consensus/MiniProtocol/LocalStateQuery/Server.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ import Ouroboros.Consensus.Ledger.Query (Query (..))
3737
import Ouroboros.Consensus.MiniProtocol.LocalStateQuery.Server
3838
import Ouroboros.Consensus.Node.ProtocolInfo (NumCoreNodes (..))
3939
import Ouroboros.Consensus.NodeId
40+
import Ouroboros.Consensus.Peras.Weight (emptyPerasWeightSnapshot)
4041
import Ouroboros.Consensus.Protocol.BFT
4142
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.BlockCache as BlockCache
4243
import Ouroboros.Consensus.Storage.ImmutableDB.Stream hiding
@@ -100,7 +101,7 @@ prop_localStateQueryServer ::
100101
prop_localStateQueryServer k bt p (Positive (Small n)) = checkOutcome k chain actualOutcome
101102
where
102103
chain :: Chain TestBlock
103-
chain = treePreferredChain bt
104+
chain = treePreferredChain emptyPerasWeightSnapshot bt
104105

105106
points :: [Target (Point TestBlock)]
106107
points =

ouroboros-consensus/test/storage-test/Test/Ouroboros/Storage/ChainDB/Model.hs

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -113,6 +113,7 @@ import Ouroboros.Consensus.HeaderValidation
113113
import Ouroboros.Consensus.Ledger.Abstract
114114
import Ouroboros.Consensus.Ledger.Extended
115115
import Ouroboros.Consensus.Ledger.SupportsProtocol
116+
import Ouroboros.Consensus.Peras.SelectView
116117
import Ouroboros.Consensus.Peras.Weight
117118
import Ouroboros.Consensus.Protocol.Abstract
118119
import Ouroboros.Consensus.Protocol.MockChainSel
@@ -571,9 +572,15 @@ chainSelection cfg m =
571572
. selectChain
572573
(Proxy @(BlockProtocol blk))
573574
(projectChainOrderConfig (configBlock cfg))
574-
(selectView (configBlock cfg) . getHeader)
575+
( weightedSelectView (configBlock cfg) weights
576+
. Chain.toAnchoredFragment
577+
. fmap getHeader
578+
)
575579
(currentChain m)
576580
$ consideredCandidates
581+
where
582+
-- TODO enrich with Peras weights/certs
583+
weights = emptyPerasWeightSnapshot
577584

578585
-- We update the set of valid blocks with all valid blocks on all candidate
579586
-- chains that are considered by the modeled chain selection. This ensures
@@ -1151,7 +1158,11 @@ wipeVolatileDB cfg m =
11511158
$ selectChain
11521159
(Proxy @(BlockProtocol blk))
11531160
(projectChainOrderConfig (configBlock cfg))
1154-
(selectView (configBlock cfg) . getHeader)
1161+
-- Weight is inconsequential as there is only a single candidate.
1162+
( weightedSelectView (configBlock cfg) emptyPerasWeightSnapshot
1163+
. Chain.toAnchoredFragment
1164+
. fmap getHeader
1165+
)
11551166
Chain.genesis
11561167
$ snd
11571168
$ validChains cfg m (immutableDbBlocks m)

0 commit comments

Comments
 (0)