Skip to content

Commit e12f5ae

Browse files
agustinmistaamesgengeo2atbagrel1nbacquey
committed
Tweak HasPerasCertX typeclasses
This commit simplifies the interface of the HasPerasCertX typeclasses, removing the StandardHash superclass constraint, and splitting them into several smaller typeclasses. 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 fc415f4 commit e12f5ae

File tree

7 files changed

+34
-27
lines changed

7 files changed

+34
-27
lines changed

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

Lines changed: 25 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,8 @@
33
{-# LANGUAGE DerivingVia #-}
44
{-# LANGUAGE FlexibleContexts #-}
55
{-# LANGUAGE FlexibleInstances #-}
6+
{-# LANGUAGE FunctionalDependencies #-}
67
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
7-
{-# LANGUAGE MultiParamTypeClasses #-}
88
{-# LANGUAGE NamedFieldPuns #-}
99
{-# LANGUAGE ScopedTypeVariables #-}
1010
{-# LANGUAGE TypeApplications #-}
@@ -17,10 +17,9 @@ module Ouroboros.Consensus.Block.SupportsPeras
1717
, BlockSupportsPeras (..)
1818
, PerasCert (..)
1919
, ValidatedPerasCert (..)
20-
, HasPerasCert (..)
21-
, getPerasCertRound
22-
, getPerasCertBoostedBlock
23-
, getPerasCertBoost
20+
, HasPerasCertRound (..)
21+
, HasPerasCertBoostedBlock (..)
22+
, HasPerasCertBoost (..)
2423

2524
-- * Convenience re-exports
2625
, module Ouroboros.Consensus.Peras.Params
@@ -134,20 +133,29 @@ instance Serialise (HeaderHash blk) => Serialise (PerasCert blk) where
134133
pcCertBoostedBlock <- decode
135134
pure $ PerasCert{pcCertRound, pcCertBoostedBlock}
136135

137-
class StandardHash blk => HasPerasCert cert blk where
138-
getPerasCert :: cert blk -> PerasCert blk
136+
-- | Extract the certificate round from a Peras certificate container
137+
class HasPerasCertRound cert where
138+
getPerasCertRound :: cert -> PerasRoundNo
139139

140-
instance StandardHash blk => HasPerasCert PerasCert blk where
141-
getPerasCert = id
140+
instance HasPerasCertRound (PerasCert blk) where
141+
getPerasCertRound = pcCertRound
142142

143-
instance StandardHash blk => HasPerasCert ValidatedPerasCert blk where
144-
getPerasCert = vpcCert
143+
instance HasPerasCertRound (ValidatedPerasCert blk) where
144+
getPerasCertRound = getPerasCertRound . vpcCert
145145

146-
getPerasCertRound :: HasPerasCert cert blk => cert blk -> PerasRoundNo
147-
getPerasCertRound = pcCertRound . getPerasCert
146+
-- | Extract the boosted block point from a Peras certificate container
147+
class HasPerasCertBoostedBlock cert blk | cert -> blk where
148+
getPerasCertBoostedBlock :: cert -> Point blk
148149

149-
getPerasCertBoostedBlock :: HasPerasCert cert blk => cert blk -> Point blk
150-
getPerasCertBoostedBlock = pcCertBoostedBlock . getPerasCert
150+
instance HasPerasCertBoostedBlock (PerasCert blk) blk where
151+
getPerasCertBoostedBlock = pcCertBoostedBlock
151152

152-
getPerasCertBoost :: ValidatedPerasCert blk -> PerasWeight
153-
getPerasCertBoost = vpcCertBoost
153+
instance HasPerasCertBoostedBlock (ValidatedPerasCert blk) blk where
154+
getPerasCertBoostedBlock = getPerasCertBoostedBlock . vpcCert
155+
156+
-- | Extract the certificate boost from a Peras certificate container
157+
class HasPerasCertBoost cert where
158+
getPerasCertBoost :: cert -> PerasWeight
159+
160+
instance HasPerasCertBoost (ValidatedPerasCert blk) where
161+
getPerasCertBoost = vpcCertBoost

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/MiniProtocol/ObjectDiffusion/ObjectPool/PerasCert.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ takeAscMap :: Int -> Map k v -> Map k v
3131
takeAscMap n = Map.fromDistinctAscList . take n . Map.toAscList
3232

3333
makePerasCertPoolReaderFromSnapshot ::
34-
(IOLike m, StandardHash blk) =>
34+
IOLike m =>
3535
STM m (PerasCertSnapshot blk) ->
3636
ObjectPoolReader PerasRoundNo (PerasCert blk) PerasCertTicketNo m
3737
makePerasCertPoolReaderFromSnapshot getCertSnapshot =
@@ -43,15 +43,15 @@ makePerasCertPoolReaderFromSnapshot getCertSnapshot =
4343
let certsAfterLastKnown =
4444
PerasCertDB.getCertsAfter certSnapshot lastKnown
4545
let loadCertsAfterLastKnown =
46-
pure (getPerasCert <$> takeAscMap (fromIntegral limit) certsAfterLastKnown)
46+
pure (vpcCert <$> takeAscMap (fromIntegral limit) certsAfterLastKnown)
4747
pure $
4848
if Map.null certsAfterLastKnown
4949
then Nothing
5050
else Just loadCertsAfterLastKnown
5151
}
5252

5353
makePerasCertPoolReaderFromCertDB ::
54-
(IOLike m, StandardHash blk) =>
54+
IOLike m =>
5555
PerasCertDB m blk -> ObjectPoolReader PerasRoundNo (PerasCert blk) PerasCertTicketNo m
5656
makePerasCertPoolReaderFromCertDB perasCertDB =
5757
makePerasCertPoolReaderFromSnapshot (PerasCertDB.getCertSnapshot perasCertDB)
@@ -71,7 +71,7 @@ makePerasCertPoolWriterFromCertDB perasCertDB =
7171
}
7272

7373
makePerasCertPoolReaderFromChainDB ::
74-
(IOLike m, StandardHash blk) =>
74+
IOLike m =>
7575
ChainDB m blk -> ObjectPoolReader PerasRoundNo (PerasCert blk) PerasCertTicketNo m
7676
makePerasCertPoolReaderFromChainDB chainDB =
7777
makePerasCertPoolReaderFromSnapshot (ChainDB.getPerasCertSnapshot chainDB)

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/ChainDB/Impl/ChainSel.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -326,7 +326,7 @@ addBlockAsync CDB{cdbTracer, cdbChainSelQueue} =
326326

327327
addPerasCertAsync ::
328328
forall m blk.
329-
(IOLike m, HasHeader blk) =>
329+
IOLike m =>
330330
ChainDbEnv m blk ->
331331
ValidatedPerasCert blk ->
332332
m (AddPerasCertPromise m)

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/ChainDB/Impl/Types.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -606,7 +606,7 @@ addBlockToAdd tracer (ChainSelQueue{varChainSelQueue, varChainSelPoints}) punish
606606

607607
-- | Add a Peras certificate to the background queue.
608608
addPerasCertToQueue ::
609-
(IOLike m, StandardHash blk) =>
609+
IOLike m =>
610610
Tracer m (TraceAddPerasCertEvent blk) ->
611611
ChainSelQueue m blk ->
612612
ValidatedPerasCert blk ->

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/PerasCertDB/Impl.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -221,7 +221,7 @@ implGetCertSnapshot PerasCertDbEnv{pcdbVolatileState} =
221221

222222
implGarbageCollect ::
223223
forall m blk.
224-
(IOLike m, StandardHash blk) =>
224+
IOLike m =>
225225
PerasCertDbEnv m blk -> SlotNo -> m ()
226226
implGarbageCollect PerasCertDbEnv{pcdbVolatileState} slot =
227227
-- No need to update the 'Fingerprint' as we only remove certificates that do

ouroboros-consensus/test/consensus-test/Test/Consensus/MiniProtocol/ObjectDiffusion/PerasCert/Smoke.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -140,7 +140,7 @@ prop_smoke =
140140
let rawContent =
141141
Map.toAscList $
142142
PerasCertDB.getCertsAfter snap (PerasCertDB.zeroPerasCertTicketNo)
143-
pure $ getPerasCert . snd <$> rawContent
143+
pure $ vpcCert . snd <$> rawContent
144144

145145
return (outboundPoolReader, inboundPoolWriter, getAllInboundPoolContent)
146146
in

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

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,6 @@ addCert model@Model{certs} cert
4949
| otherwise = model{certs = Set.insert cert certs}
5050

5151
hasRoundNo ::
52-
StandardHash blk =>
5352
Set (ValidatedPerasCert blk) ->
5453
ValidatedPerasCert blk ->
5554
Bool
@@ -65,7 +64,7 @@ getWeightSnapshot Model{certs} =
6564
| cert <- Set.toList certs
6665
]
6766

68-
garbageCollect :: StandardHash blk => SlotNo -> Model blk -> Model blk
67+
garbageCollect :: SlotNo -> Model blk -> Model blk
6968
garbageCollect slot model@Model{certs} =
7069
model{certs = Set.filter keepCert certs}
7170
where

0 commit comments

Comments
 (0)