1+ {-# LANGUAGE DataKinds #-}
12{-# LANGUAGE DeriveAnyClass #-}
23{-# LANGUAGE DeriveGeneric #-}
34{-# LANGUAGE DerivingVia #-}
1415module 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+ , HasPerasVoteStake (.. )
36+ , HasPerasVoteTarget (.. )
37+ , HasPerasVoteId (.. )
2338
2439 -- * Convenience re-exports
2540 , module Ouroboros.Consensus.Peras.Params
2641 ) where
2742
43+ import qualified Cardano.Binary as KeyHash
44+ import Cardano.Ledger.Hashes (KeyHash , KeyRole (.. ))
2845import Codec.Serialise (Serialise (.. ))
2946import Codec.Serialise.Decoding (decodeListLenOf )
3047import Codec.Serialise.Encoding (encodeListLen )
3148import Data.Coerce (coerce )
49+ import qualified Data.Map as Map
50+ import Data.Map.Strict (Map )
51+ import Data.Monoid (Sum (.. ))
3252import Data.Proxy (Proxy (.. ))
3353import Data.Word (Word64 )
3454import GHC.Generics (Generic )
@@ -40,6 +60,12 @@ import Ouroboros.Consensus.Util
4060import Ouroboros.Consensus.Util.Condense
4161import Quiet (Quiet (.. ))
4262
63+ {- ------------------------------------------------------------------------------
64+ -- * Peras types
65+ -------------------------------------------------------------------------------}
66+
67+ -- ** Round numbers
68+
4369newtype PerasRoundNo = PerasRoundNo { unPerasRoundNo :: Word64 }
4470 deriving Show via Quiet PerasRoundNo
4571 deriving stock Generic
@@ -57,14 +83,78 @@ onPerasRoundNo ::
5783 (PerasRoundNo -> PerasRoundNo -> PerasRoundNo )
5884onPerasRoundNo = coerce
5985
60- -- TODO using 'Validated' for extra safety? Or some @.Unsafe@ module?
86+ -- ** Stake pool distributions
87+
88+ newtype PerasVoterId = PerasVoterId
89+ { unPerasVoterId :: KeyHash StakePool
90+ }
91+ deriving newtype NoThunks
92+ deriving stock (Eq , Ord , Generic )
93+ deriving Show via Quiet PerasVoterId
94+
95+ -- NOTE: At the moment there is no consensus from researchers/engineers on how
96+ -- we go from the absolute stake of a voter in the ledger to the relative stake
97+ -- of their vote in the voting commitee (given that the quorum is expressed as
98+ -- a relative value of the voting commitee total stake).
99+ --
100+ -- So, for now you can consider this 'Rational' as the best approximation we
101+ -- have at the moment of the concrete type for a relative vote stake that can be
102+ -- compared to the quorum threshold value (also currently a 'Rational').
103+ newtype PerasVoteStake = PerasVoteStake
104+ { unPerasVoteStake :: Rational
105+ }
106+ deriving newtype (Eq , Ord , Num , Fractional , NoThunks , Serialise )
107+ deriving stock Generic
108+ deriving Show via Quiet PerasVoteStake
109+ deriving Semigroup via Sum Rational
110+ deriving Monoid via Sum Rational
111+
112+ newtype PerasVoteStakeDistr = PerasVoteStakeDistr
113+ { unPerasVoteStakeDistr :: Map PerasVoterId PerasVoteStake
114+ }
115+ deriving newtype NoThunks
116+ deriving stock (Show , Eq , Generic )
117+
118+ data PerasVoteTarget blk = PerasVoteTarget
119+ { pvtRoundNo :: ! PerasRoundNo
120+ , pvtBlock :: ! (Point blk )
121+ }
122+ deriving stock (Show , Eq , Ord , Generic )
123+ deriving anyclass NoThunks
124+
125+ data PerasVoteId blk = PerasVoteId
126+ { pviRoundNo :: ! PerasRoundNo
127+ , pviVoterId :: ! PerasVoterId
128+ }
129+ deriving stock (Show , Eq , Ord , Generic )
130+ deriving anyclass NoThunks
131+
132+ -- | Lookup the stake of a vote cast by a member of a given stake distribution.
133+ lookupPerasVoteStake ::
134+ PerasVote blk ->
135+ PerasVoteStakeDistr ->
136+ Maybe PerasVoteStake
137+ lookupPerasVoteStake vote distr =
138+ Map. lookup
139+ (pvVoteVoterId vote)
140+ (unPerasVoteStakeDistr distr)
141+
142+ -- ** Validated types
143+
61144data ValidatedPerasCert blk = ValidatedPerasCert
62145 { vpcCert :: ! (PerasCert blk )
63146 , vpcCertBoost :: ! PerasWeight
64147 }
65148 deriving stock (Show , Eq , Ord , Generic )
66149 deriving anyclass NoThunks
67150
151+ data ValidatedPerasVote blk = ValidatedPerasVote
152+ { vpvVote :: ! (PerasVote blk )
153+ , vpvVoteStake :: ! PerasVoteStake
154+ }
155+ deriving stock (Show , Eq , Ord , Generic )
156+ deriving anyclass NoThunks
157+
68158{- ------------------------------------------------------------------------------
69159-- * BlockSupportsPeras class
70160-------------------------------------------------------------------------------}
@@ -79,13 +169,29 @@ class
79169
80170 data PerasCert blk
81171
172+ data PerasVote blk
173+
82174 data PerasValidationErr blk
83175
176+ data PerasForgeErr blk
177+
84178 validatePerasCert ::
85179 PerasCfg blk ->
86180 PerasCert blk ->
87181 Either (PerasValidationErr blk ) (ValidatedPerasCert blk )
88182
183+ validatePerasVote ::
184+ PerasCfg blk ->
185+ PerasVoteStakeDistr ->
186+ PerasVote blk ->
187+ Either (PerasValidationErr blk ) (ValidatedPerasVote blk )
188+
189+ forgePerasCert ::
190+ PerasCfg blk ->
191+ PerasVoteTarget blk ->
192+ [ValidatedPerasVote blk ] ->
193+ Either (PerasForgeErr blk ) (ValidatedPerasCert blk )
194+
89195-- TODO: degenerate instance for all blks to get things to compile
90196-- see https://github.com/tweag/cardano-peras/issues/73
91197instance StandardHash blk => BlockSupportsPeras blk where
@@ -98,12 +204,27 @@ instance StandardHash blk => BlockSupportsPeras blk where
98204 deriving stock (Generic , Eq , Ord , Show )
99205 deriving anyclass NoThunks
100206
207+ data PerasVote blk = PerasVote
208+ { pvVoteRound :: PerasRoundNo
209+ , pvVoteBlock :: Point blk
210+ , pvVoteVoterId :: PerasVoterId
211+ }
212+ deriving stock (Generic , Eq , Ord , Show )
213+ deriving anyclass NoThunks
214+
101215 -- TODO: enrich with actual error types
102216 -- see https://github.com/tweag/cardano-peras/issues/120
103217 data PerasValidationErr blk
104218 = PerasValidationErr
105219 deriving stock (Show , Eq )
106220
221+ -- TODO: enrich with actual error types
222+ -- see https://github.com/tweag/cardano-peras/issues/120
223+ data PerasForgeErr blk
224+ = PerasForgeErrInsufficientVotes
225+ | PerasForgeErrTargetMismatch
226+ deriving stock (Show , Eq )
227+
107228 -- TODO: perform actual validation against all
108229 -- possible 'PerasValidationErr' variants
109230 -- see https://github.com/tweag/cardano-peras/issues/120
@@ -114,9 +235,54 @@ instance StandardHash blk => BlockSupportsPeras blk where
114235 , vpcCertBoost = perasWeight params
115236 }
116237
238+ -- TODO: perform actual validation against all
239+ -- possible 'PerasValidationErr' variants
240+ -- see https://github.com/tweag/cardano-peras/issues/120
241+ validatePerasVote _params stakeDistr vote
242+ | Just stake <- lookupPerasVoteStake vote stakeDistr =
243+ Right
244+ ValidatedPerasVote
245+ { vpvVote = vote
246+ , vpvVoteStake = stake
247+ }
248+ | otherwise =
249+ Left PerasValidationErr
250+
251+ -- TODO: perform actual validation against all
252+ -- possible 'PerasForgeErr' variants
253+ -- see https://github.com/tweag/cardano-peras/issues/120
254+ forgePerasCert params target votes
255+ | not allVotersMatchTarget =
256+ Left PerasForgeErrTargetMismatch
257+ | not votesHaveEnoughStake =
258+ Left PerasForgeErrInsufficientVotes
259+ | otherwise =
260+ return $
261+ ValidatedPerasCert
262+ { vpcCert =
263+ PerasCert
264+ { pcCertRound = pvtRoundNo target
265+ , pcCertBoostedBlock = pvtBlock target
266+ }
267+ , vpcCertBoost = perasWeight params
268+ }
269+ where
270+ totalVotesStake =
271+ mconcat (vpvVoteStake <$> votes)
272+
273+ votesHaveEnoughStake =
274+ unPerasVoteStake totalVotesStake
275+ >= unPerasQuorumStakeThreshold (perasQuorumStakeThreshold params)
276+
277+ allVotersMatchTarget =
278+ all ((target == ) . getPerasVoteTarget) votes
279+
117280instance ShowProxy blk => ShowProxy (PerasCert blk ) where
118281 showProxy _ = " PerasCert " <> showProxy (Proxy @ blk )
119282
283+ instance ShowProxy blk => ShowProxy (PerasVote blk ) where
284+ showProxy _ = " PerasVote " <> showProxy (Proxy @ blk )
285+
120286instance Serialise (HeaderHash blk ) => Serialise (PerasCert blk ) where
121287 encode PerasCert {pcCertRound, pcCertBoostedBlock} =
122288 encodeListLen 2
@@ -128,6 +294,19 @@ instance Serialise (HeaderHash blk) => Serialise (PerasCert blk) where
128294 pcCertBoostedBlock <- decode
129295 pure $ PerasCert {pcCertRound, pcCertBoostedBlock}
130296
297+ instance Serialise (HeaderHash blk ) => Serialise (PerasVote blk ) where
298+ encode PerasVote {pvVoteRound, pvVoteBlock, pvVoteVoterId} =
299+ encodeListLen 3
300+ <> encode pvVoteRound
301+ <> encode pvVoteBlock
302+ <> KeyHash. toCBOR (unPerasVoterId pvVoteVoterId)
303+ decode = do
304+ decodeListLenOf 3
305+ pvVoteRound <- decode
306+ pvVoteBlock <- decode
307+ pvVoteVoterId <- PerasVoterId <$> KeyHash. fromCBOR
308+ pure $ PerasVote {pvVoteRound, pvVoteBlock, pvVoteVoterId}
309+
131310-- | Extract the certificate round from a Peras certificate container
132311class HasPerasCertRound cert where
133312 getPerasCertRound :: cert -> PerasRoundNo
@@ -172,3 +351,104 @@ instance
172351 HasPerasCertBoost (WithArrivalTime cert )
173352 where
174353 getPerasCertBoost = getPerasCertBoost . forgetArrivalTime
354+
355+ -- | Extract the vote round from a Peras vote container
356+ class HasPerasVoteRound vote where
357+ getPerasVoteRound :: vote -> PerasRoundNo
358+
359+ instance HasPerasVoteRound (PerasVote blk ) where
360+ getPerasVoteRound = pvVoteRound
361+
362+ instance HasPerasVoteRound (ValidatedPerasVote blk ) where
363+ getPerasVoteRound = getPerasVoteRound . vpvVote
364+
365+ instance
366+ HasPerasVoteRound vote =>
367+ HasPerasVoteRound (WithArrivalTime vote )
368+ where
369+ getPerasVoteRound = getPerasVoteRound . forgetArrivalTime
370+
371+ -- | Extract the vote block point from a Peras vote container
372+ class HasPerasVoteBlock vote blk | vote -> blk where
373+ getPerasVoteBlock :: vote -> Point blk
374+
375+ instance HasPerasVoteBlock (PerasVote blk ) blk where
376+ getPerasVoteBlock = pvVoteBlock
377+
378+ instance HasPerasVoteBlock (ValidatedPerasVote blk ) blk where
379+ getPerasVoteBlock = getPerasVoteBlock . vpvVote
380+
381+ instance
382+ HasPerasVoteBlock vote blk =>
383+ HasPerasVoteBlock (WithArrivalTime vote ) blk
384+ where
385+ getPerasVoteBlock = getPerasVoteBlock . forgetArrivalTime
386+
387+ -- | Extract the stake pool ID from a Peras vote container
388+ class HasPerasVoteVoterId vote where
389+ getPerasVoteVoterId :: vote -> PerasVoterId
390+
391+ instance HasPerasVoteVoterId (PerasVote blk ) where
392+ getPerasVoteVoterId = pvVoteVoterId
393+
394+ instance HasPerasVoteVoterId (ValidatedPerasVote blk ) where
395+ getPerasVoteVoterId = getPerasVoteVoterId . vpvVote
396+
397+ instance
398+ HasPerasVoteVoterId vote =>
399+ HasPerasVoteVoterId (WithArrivalTime vote )
400+ where
401+ getPerasVoteVoterId = getPerasVoteVoterId . forgetArrivalTime
402+
403+ -- | Extract the vote stake from a validated Peras vote container
404+ class HasPerasVoteStake vote where
405+ getPerasVoteStake :: vote -> PerasVoteStake
406+
407+ instance HasPerasVoteStake (ValidatedPerasVote blk ) where
408+ getPerasVoteStake = vpvVoteStake
409+
410+ instance
411+ HasPerasVoteStake vote =>
412+ HasPerasVoteStake (WithArrivalTime vote )
413+ where
414+ getPerasVoteStake = getPerasVoteStake . forgetArrivalTime
415+
416+ -- | Extract the vote target from a Peras vote container
417+ class HasPerasVoteTarget vote blk | vote -> blk where
418+ getPerasVoteTarget :: vote -> PerasVoteTarget blk
419+
420+ instance HasPerasVoteTarget (PerasVote blk ) blk where
421+ getPerasVoteTarget vote =
422+ PerasVoteTarget
423+ { pvtRoundNo = pvVoteRound vote
424+ , pvtBlock = pvVoteBlock vote
425+ }
426+
427+ instance HasPerasVoteTarget (ValidatedPerasVote blk ) blk where
428+ getPerasVoteTarget = getPerasVoteTarget . vpvVote
429+
430+ instance
431+ HasPerasVoteTarget vote blk =>
432+ HasPerasVoteTarget (WithArrivalTime vote ) blk
433+ where
434+ getPerasVoteTarget = getPerasVoteTarget . forgetArrivalTime
435+
436+ -- | Extract the vote ID from a Peras vote container
437+ class HasPerasVoteId vote blk | vote -> blk where
438+ getPerasVoteId :: vote -> PerasVoteId blk
439+
440+ instance HasPerasVoteId (PerasVote blk ) blk where
441+ getPerasVoteId vote =
442+ PerasVoteId
443+ { pviRoundNo = pvVoteRound vote
444+ , pviVoterId = pvVoteVoterId vote
445+ }
446+
447+ instance HasPerasVoteId (ValidatedPerasVote blk ) blk where
448+ getPerasVoteId = getPerasVoteId . vpvVote
449+
450+ instance
451+ HasPerasVoteId vote blk =>
452+ HasPerasVoteId (WithArrivalTime vote ) blk
453+ where
454+ getPerasVoteId = getPerasVoteId . forgetArrivalTime
0 commit comments