Skip to content

Commit 24c7a88

Browse files
agustinmistaamesgengeo2atbagrel1nbacquey
committed
Introduce Peras votes and certificate forging API
This commit introduces a couple of new types to represent Peras votes and their corresponding certificate forging API. Notably, this requires an initial representation of notions like vote targets, vote stakes and stake distributions over multiple stake pools. Co-authored-by: Agustin Mista <agustin.mista@moduscreate.com> Co-authored-by: Alexander Esgen <alexander.esgen@iohk.io> Co-authored-by: Georgy Lukyanov <georgy.lukyanov@iohk.io> Co-authored-by: Thomas BAGREL <thomas.bagrel@tweag.io> Co-authored-by: Nicolas BACQUEY <nicolas.bacquey@tweag.io>
1 parent d51b1a1 commit 24c7a88

File tree

3 files changed

+303
-1
lines changed

3 files changed

+303
-1
lines changed

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Block/SupportsPeras.hs

Lines changed: 272 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE DataKinds #-}
12
{-# LANGUAGE DeriveAnyClass #-}
23
{-# LANGUAGE DeriveGeneric #-}
34
{-# LANGUAGE DerivingVia #-}
@@ -14,21 +15,39 @@
1415
module Ouroboros.Consensus.Block.SupportsPeras
1516
( PerasRoundNo (..)
1617
, onPerasRoundNo
18+
, PerasVoteId (..)
19+
, PerasVoteTarget (..)
20+
, PerasVoterId (..)
21+
, PerasVoteStake (..)
22+
, PerasVoteStakeDistr (..)
23+
, lookupPerasVoteStake
1724
, BlockSupportsPeras (..)
1825
, PerasCert (..)
26+
, PerasVote (..)
1927
, ValidatedPerasCert (..)
28+
, ValidatedPerasVote (..)
2029
, HasPerasCertRound (..)
2130
, HasPerasCertBoostedBlock (..)
2231
, HasPerasCertBoost (..)
32+
, HasPerasVoteRound (..)
33+
, HasPerasVoteBlock (..)
34+
, HasPerasVoteVoterId (..)
35+
, HasPerasVoteTarget (..)
36+
, HasPerasVoteId (..)
2337

2438
-- * Convenience re-exports
2539
, module Ouroboros.Consensus.Peras.Params
2640
) where
2741

42+
import qualified Cardano.Binary as KeyHash
43+
import Cardano.Ledger.Hashes (KeyHash, KeyRole (..))
2844
import Codec.Serialise (Serialise (..))
2945
import Codec.Serialise.Decoding (decodeListLenOf)
3046
import Codec.Serialise.Encoding (encodeListLen)
3147
import Data.Coerce (coerce)
48+
import qualified Data.Map as Map
49+
import Data.Map.Strict (Map)
50+
import Data.Monoid (Sum (..))
3251
import Data.Proxy (Proxy (..))
3352
import Data.Word (Word64)
3453
import GHC.Generics (Generic)
@@ -40,6 +59,12 @@ import Ouroboros.Consensus.Util
4059
import Ouroboros.Consensus.Util.Condense
4160
import Quiet (Quiet (..))
4261

62+
{-------------------------------------------------------------------------------
63+
-- * Peras types
64+
-------------------------------------------------------------------------------}
65+
66+
-- ** Round numbers
67+
4368
newtype PerasRoundNo = PerasRoundNo {unPerasRoundNo :: Word64}
4469
deriving Show via Quiet PerasRoundNo
4570
deriving stock Generic
@@ -57,14 +82,70 @@ onPerasRoundNo ::
5782
(PerasRoundNo -> PerasRoundNo -> PerasRoundNo)
5883
onPerasRoundNo = coerce
5984

60-
-- TODO using 'Validated' for extra safety? Or some @.Unsafe@ module?
85+
-- ** Stake pool distributions
86+
87+
newtype PerasVoterId = PerasVoterId
88+
{ unPerasVoterId :: KeyHash StakePool
89+
}
90+
deriving newtype NoThunks
91+
deriving stock (Eq, Ord, Generic)
92+
deriving Show via Quiet PerasVoterId
93+
94+
newtype PerasVoteStake = PerasVoteStake
95+
{ unPerasVoteStake :: Rational
96+
}
97+
deriving newtype (Enum, Eq, Ord, Num, Fractional, NoThunks, Serialise)
98+
deriving stock Generic
99+
deriving Show via Quiet PerasVoteStake
100+
deriving Semigroup via Sum Rational
101+
deriving Monoid via Sum Rational
102+
103+
newtype PerasVoteStakeDistr = PerasVoteStakeDistr
104+
{ unPerasVoteStakeDistr :: Map PerasVoterId PerasVoteStake
105+
}
106+
deriving newtype NoThunks
107+
deriving stock (Show, Eq, Generic)
108+
109+
data PerasVoteTarget blk = PerasVoteTarget
110+
{ pvtRoundNo :: !PerasRoundNo
111+
, pvtBlock :: !(Point blk)
112+
}
113+
deriving stock (Show, Eq, Ord, Generic)
114+
deriving anyclass NoThunks
115+
116+
data PerasVoteId blk = PerasVoteId
117+
{ pviRoundNo :: !PerasRoundNo
118+
, pviVoterId :: !PerasVoterId
119+
}
120+
deriving stock (Show, Eq, Ord, Generic)
121+
deriving anyclass NoThunks
122+
123+
-- | Lookup the stake of vote casted by a member of a given stake distribution.
124+
lookupPerasVoteStake ::
125+
PerasVote blk ->
126+
PerasVoteStakeDistr ->
127+
Maybe PerasVoteStake
128+
lookupPerasVoteStake vote distr =
129+
Map.lookup
130+
(pvVoteVoterId vote)
131+
(unPerasVoteStakeDistr distr)
132+
133+
-- ** Validated types
134+
61135
data ValidatedPerasCert blk = ValidatedPerasCert
62136
{ vpcCert :: !(PerasCert blk)
63137
, vpcCertBoost :: !PerasWeight
64138
}
65139
deriving stock (Show, Eq, Ord, Generic)
66140
deriving anyclass NoThunks
67141

142+
data ValidatedPerasVote blk = ValidatedPerasVote
143+
{ vpvVote :: !(PerasVote blk)
144+
, vpvVoteStake :: !PerasVoteStake
145+
}
146+
deriving stock (Show, Eq, Ord, Generic)
147+
deriving anyclass NoThunks
148+
68149
{-------------------------------------------------------------------------------
69150
-- * BlockSupportsPeras class
70151
-------------------------------------------------------------------------------}
@@ -79,13 +160,29 @@ class
79160

80161
data PerasCert blk
81162

163+
data PerasVote blk
164+
82165
data PerasValidationErr blk
83166

167+
data PerasForgeErr blk
168+
84169
validatePerasCert ::
85170
PerasCfg blk ->
86171
PerasCert blk ->
87172
Either (PerasValidationErr blk) (ValidatedPerasCert blk)
88173

174+
validatePerasVote ::
175+
PerasCfg blk ->
176+
PerasVoteStakeDistr ->
177+
PerasVote blk ->
178+
Either (PerasValidationErr blk) (ValidatedPerasVote blk)
179+
180+
forgePerasCert ::
181+
PerasCfg blk ->
182+
PerasVoteTarget blk ->
183+
[ValidatedPerasVote blk] ->
184+
Either (PerasForgeErr blk) (ValidatedPerasCert blk)
185+
89186
-- TODO: degenerate instance for all blks to get things to compile
90187
-- see https://github.com/tweag/cardano-peras/issues/73
91188
instance StandardHash blk => BlockSupportsPeras blk where
@@ -98,12 +195,27 @@ instance StandardHash blk => BlockSupportsPeras blk where
98195
deriving stock (Generic, Eq, Ord, Show)
99196
deriving anyclass NoThunks
100197

198+
data PerasVote blk = PerasVote
199+
{ pvVoteRound :: PerasRoundNo
200+
, pvVoteBlock :: Point blk
201+
, pvVoteVoterId :: PerasVoterId
202+
}
203+
deriving stock (Generic, Eq, Ord, Show)
204+
deriving anyclass NoThunks
205+
101206
-- TODO: enrich with actual error types
102207
-- see https://github.com/tweag/cardano-peras/issues/120
103208
data PerasValidationErr blk
104209
= PerasValidationErr
105210
deriving stock (Show, Eq)
106211

212+
-- TODO: enrich with actual error types
213+
-- see https://github.com/tweag/cardano-peras/issues/120
214+
data PerasForgeErr blk
215+
= PerasForgeErrInsufficientVotes
216+
| PerasForgeErrTargetMismatch
217+
deriving stock (Show, Eq)
218+
107219
-- TODO: perform actual validation against all
108220
-- possible 'PerasValidationErr' variants
109221
-- see https://github.com/tweag/cardano-peras/issues/120
@@ -114,9 +226,54 @@ instance StandardHash blk => BlockSupportsPeras blk where
114226
, vpcCertBoost = perasWeight params
115227
}
116228

229+
-- TODO: perform actual validation against all
230+
-- possible 'PerasValidationErr' variants
231+
-- see https://github.com/tweag/cardano-peras/issues/120
232+
validatePerasVote _params stakeDistr vote
233+
| Just stake <- lookupPerasVoteStake vote stakeDistr =
234+
Right
235+
ValidatedPerasVote
236+
{ vpvVote = vote
237+
, vpvVoteStake = stake
238+
}
239+
| otherwise =
240+
Left PerasValidationErr
241+
242+
-- TODO: perform actual validation against all
243+
-- possible 'PerasForgeErr' variants
244+
-- see https://github.com/tweag/cardano-peras/issues/120
245+
forgePerasCert params target votes
246+
| not allVotersMatchTarget =
247+
Left PerasForgeErrTargetMismatch
248+
| not votesHaveEnoughStake =
249+
Left PerasForgeErrInsufficientVotes
250+
| otherwise =
251+
return $
252+
ValidatedPerasCert
253+
{ vpcCert =
254+
PerasCert
255+
{ pcCertRound = pvtRoundNo target
256+
, pcCertBoostedBlock = pvtBlock target
257+
}
258+
, vpcCertBoost = perasWeight params
259+
}
260+
where
261+
totalVotesStake =
262+
mconcat (vpvVoteStake <$> votes)
263+
264+
votesHaveEnoughStake =
265+
unPerasVoteStake totalVotesStake
266+
>= unPerasQuorumStakeThreshold (perasQuorumStakeThreshold params)
267+
268+
allVotersMatchTarget =
269+
all ((target ==) . getPerasVoteTarget) votes
270+
117271
instance ShowProxy blk => ShowProxy (PerasCert blk) where
118272
showProxy _ = "PerasCert " <> showProxy (Proxy @blk)
119273

274+
instance ShowProxy blk => ShowProxy (PerasVote blk) where
275+
showProxy _ = "PerasVote " <> showProxy (Proxy @blk)
276+
120277
instance Serialise (HeaderHash blk) => Serialise (PerasCert blk) where
121278
encode PerasCert{pcCertRound, pcCertBoostedBlock} =
122279
encodeListLen 2
@@ -128,6 +285,19 @@ instance Serialise (HeaderHash blk) => Serialise (PerasCert blk) where
128285
pcCertBoostedBlock <- decode
129286
pure $ PerasCert{pcCertRound, pcCertBoostedBlock}
130287

288+
instance Serialise (HeaderHash blk) => Serialise (PerasVote blk) where
289+
encode PerasVote{pvVoteRound, pvVoteBlock, pvVoteVoterId} =
290+
encodeListLen 3
291+
<> encode pvVoteRound
292+
<> encode pvVoteBlock
293+
<> KeyHash.toCBOR (unPerasVoterId pvVoteVoterId)
294+
decode = do
295+
decodeListLenOf 3
296+
pvVoteRound <- decode
297+
pvVoteBlock <- decode
298+
pvVoteVoterId <- PerasVoterId <$> KeyHash.fromCBOR
299+
pure $ PerasVote{pvVoteRound, pvVoteBlock, pvVoteVoterId}
300+
131301
-- | Extract the certificate round from a Peras certificate container
132302
class HasPerasCertRound cert where
133303
getPerasCertRound :: cert -> PerasRoundNo
@@ -172,3 +342,104 @@ instance
172342
HasPerasCertBoost (WithArrivalTime cert)
173343
where
174344
getPerasCertBoost = getPerasCertBoost . forgetArrivalTime
345+
346+
-- | Extract the vote round from a Peras vote container
347+
class HasPerasVoteRound vote where
348+
getPerasVoteRound :: vote -> PerasRoundNo
349+
350+
instance HasPerasVoteRound (PerasVote blk) where
351+
getPerasVoteRound = pvVoteRound
352+
353+
instance HasPerasVoteRound (ValidatedPerasVote blk) where
354+
getPerasVoteRound = getPerasVoteRound . vpvVote
355+
356+
instance
357+
HasPerasVoteRound vote =>
358+
HasPerasVoteRound (WithArrivalTime vote)
359+
where
360+
getPerasVoteRound = getPerasVoteRound . forgetArrivalTime
361+
362+
-- | Extract the vote block point from a Peras vote container
363+
class HasPerasVoteBlock vote blk | vote -> blk where
364+
getPerasVoteBlock :: vote -> Point blk
365+
366+
instance HasPerasVoteBlock (PerasVote blk) blk where
367+
getPerasVoteBlock = pvVoteBlock
368+
369+
instance HasPerasVoteBlock (ValidatedPerasVote blk) blk where
370+
getPerasVoteBlock = getPerasVoteBlock . vpvVote
371+
372+
instance
373+
HasPerasVoteBlock vote blk =>
374+
HasPerasVoteBlock (WithArrivalTime vote) blk
375+
where
376+
getPerasVoteBlock = getPerasVoteBlock . forgetArrivalTime
377+
378+
-- | Extract the stake pool ID from a Peras vote container
379+
class HasPerasVoteVoterId vote where
380+
getPerasVoteVoterId :: vote -> PerasVoterId
381+
382+
instance HasPerasVoteVoterId (PerasVote blk) where
383+
getPerasVoteVoterId = pvVoteVoterId
384+
385+
instance HasPerasVoteVoterId (ValidatedPerasVote blk) where
386+
getPerasVoteVoterId = getPerasVoteVoterId . vpvVote
387+
388+
instance
389+
HasPerasVoteVoterId vote =>
390+
HasPerasVoteVoterId (WithArrivalTime vote)
391+
where
392+
getPerasVoteVoterId = getPerasVoteVoterId . forgetArrivalTime
393+
394+
-- | Extract the vote stake from a validated Peras vote container
395+
class HasPerasVoteStake vote where
396+
getPerasVoteStake :: vote -> PerasVoteStake
397+
398+
instance HasPerasVoteStake (ValidatedPerasVote blk) where
399+
getPerasVoteStake = vpvVoteStake
400+
401+
instance
402+
HasPerasVoteStake vote =>
403+
HasPerasVoteStake (WithArrivalTime vote)
404+
where
405+
getPerasVoteStake = getPerasVoteStake . forgetArrivalTime
406+
407+
-- | Extract the vote target from a Peras vote container
408+
class HasPerasVoteTarget vote blk | vote -> blk where
409+
getPerasVoteTarget :: vote -> PerasVoteTarget blk
410+
411+
instance HasPerasVoteTarget (PerasVote blk) blk where
412+
getPerasVoteTarget vote =
413+
PerasVoteTarget
414+
{ pvtRoundNo = pvVoteRound vote
415+
, pvtBlock = pvVoteBlock vote
416+
}
417+
418+
instance HasPerasVoteTarget (ValidatedPerasVote blk) blk where
419+
getPerasVoteTarget = getPerasVoteTarget . vpvVote
420+
421+
instance
422+
HasPerasVoteTarget vote blk =>
423+
HasPerasVoteTarget (WithArrivalTime vote) blk
424+
where
425+
getPerasVoteTarget = getPerasVoteTarget . forgetArrivalTime
426+
427+
-- | Extract the vote ID from a Peras vote container
428+
class HasPerasVoteId vote blk | vote -> blk where
429+
getPerasVoteId :: vote -> PerasVoteId blk
430+
431+
instance HasPerasVoteId (PerasVote blk) blk where
432+
getPerasVoteId vote =
433+
PerasVoteId
434+
{ pviRoundNo = pvVoteRound vote
435+
, pviVoterId = pvVoteVoterId vote
436+
}
437+
438+
instance HasPerasVoteId (ValidatedPerasVote blk) blk where
439+
getPerasVoteId = getPerasVoteId . vpvVote
440+
441+
instance
442+
HasPerasVoteId vote blk =>
443+
HasPerasVoteId (WithArrivalTime vote) blk
444+
where
445+
getPerasVoteId = getPerasVoteId . forgetArrivalTime

0 commit comments

Comments
 (0)