Skip to content

Commit 439a39d

Browse files
committed
Continuation of 'Make it build with ghc-9.12'
1 parent 7be02a8 commit 439a39d

File tree

19 files changed

+214
-230
lines changed

19 files changed

+214
-230
lines changed

cardano-db-sync/cardano-db-sync.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -154,6 +154,7 @@ library
154154
, cardano-client
155155
, cardano-crypto
156156
, cardano-crypto-class
157+
, cardano-crypto-praos
157158
, cardano-crypto-wrapper
158159
, cardano-data
159160
, cardano-db

cardano-db-sync/src/Cardano/DbSync/Cache/Epoch.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import Cardano.DbSync.Era.Shelley.Generic.StakeDist (getSecurityParameter)
1717
import Cardano.DbSync.Error (SyncNodeError (..))
1818
import Cardano.DbSync.Ledger.Types (HasLedgerEnv (..))
1919
import Cardano.DbSync.LocalStateQuery (NoLedgerEnv (..))
20+
import Cardano.Ledger.BaseTypes.NonZero (NonZero (..))
2021
import Cardano.Prelude
2122
import Control.Concurrent.Class.MonadSTM.Strict (readTVarIO, writeTVar)
2223
import Data.Map.Strict (deleteMin, insert, lookupMax, size, split)
@@ -106,7 +107,7 @@ writeToMapEpochCache syncEnv cache latestEpoch = do
106107
-- To make sure our Map Epoch doesn't get too large so we use something slightly bigger than K value "securityParam"
107108
-- and once the map gets larger than that number we delete the first inserted item making room for another Epoch.
108109
scaledMapEpoch =
109-
if size mapEpoch > fromEnum securityParam
110+
if size mapEpoch > fromEnum (unNonZero securityParam)
110111
then deleteMin mapEpoch
111112
else mapEpoch
112113

cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/Block.hs

Lines changed: 33 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,8 @@ module Cardano.DbSync.Era.Shelley.Generic.Block (
2525

2626
import qualified Cardano.Crypto.Hash as Crypto
2727
import qualified Cardano.Crypto.KES.Class as KES
28+
import Cardano.Crypto.VRF.Class (VerKeyVRF)
29+
import Cardano.Crypto.VRF.Praos (PraosVRF)
2830
import Cardano.DbSync.Era.Shelley.Generic.Tx
2931
import Cardano.DbSync.Types
3032
import Cardano.DbSync.Util.Bech32 (serialiseVerKeyVrfToBech32)
@@ -33,21 +35,21 @@ import Cardano.Ledger.Alonzo.Scripts (Prices)
3335
import qualified Cardano.Ledger.BaseTypes as Ledger
3436
import qualified Cardano.Ledger.Block as Ledger
3537
import qualified Cardano.Ledger.Core as Ledger
36-
import Cardano.Ledger.Crypto (Crypto, StandardCrypto)
37-
import Cardano.Ledger.Era (EraSegWits (..))
38-
import Cardano.Ledger.Keys (KeyHash, KeyRole (..), VerKeyVRF, hashKey)
38+
import Cardano.Protocol.Crypto (Crypto, StandardCrypto, VRF)
39+
import Cardano.Ledger.Keys (KeyHash, KeyRole (..), hashKey)
3940
import Cardano.Prelude
4041
import qualified Cardano.Protocol.TPraos.BHeader as TPraos
4142
import qualified Cardano.Protocol.TPraos.OCert as TPraos
4243
import Cardano.Slotting.Slot (SlotNo (..))
4344
import Ouroboros.Consensus.Cardano.Block (
44-
StandardAllegra,
45-
StandardAlonzo,
46-
StandardBabbage,
47-
StandardConway,
48-
StandardMary,
49-
StandardShelley,
45+
AllegraEra,
46+
AlonzoEra,
47+
BabbageEra,
48+
ConwayEra,
49+
MaryEra,
50+
ShelleyEra,
5051
)
52+
import Ouroboros.Consensus.Protocol.Praos (Praos)
5153
import qualified Ouroboros.Consensus.Protocol.Praos.Header as Praos
5254
import Ouroboros.Consensus.Shelley.Ledger.Block (ShelleyBlock)
5355
import qualified Ouroboros.Consensus.Shelley.Ledger.Block as Consensus
@@ -58,7 +60,7 @@ data Block = Block
5860
{ blkEra :: !BlockEra
5961
, blkHash :: !ByteString
6062
, blkPreviousHash :: !(Maybe ByteString) -- Nothing is used for first block after Genesis.
61-
, blkSlotLeader :: !(KeyHash 'BlockIssuer StandardCrypto)
63+
, blkSlotLeader :: !(KeyHash 'BlockIssuer)
6264
, blkSlotNo :: !SlotNo
6365
, blkBlockNo :: !BlockNo
6466
, blkSize :: !Word64
@@ -69,7 +71,7 @@ data Block = Block
6971
, blkTxs :: [Tx] -- intentionally left lazy to delay the tx transformation
7072
}
7173

72-
fromAllegraBlock :: ShelleyBlock TPraosStandard StandardAllegra -> Block
74+
fromAllegraBlock :: ShelleyBlock (TPraosStandard StandardCrypto) AllegraEra -> Block
7375
fromAllegraBlock blk =
7476
Block
7577
{ blkEra = Allegra
@@ -86,7 +88,7 @@ fromAllegraBlock blk =
8688
, blkTxs = map fromAllegraTx (getTxs blk)
8789
}
8890

89-
fromShelleyBlock :: ShelleyBlock TPraosStandard StandardShelley -> Block
91+
fromShelleyBlock :: ShelleyBlock (TPraosStandard StandardCrypto) ShelleyEra -> Block
9092
fromShelleyBlock blk =
9193
Block
9294
{ blkEra = Shelley
@@ -103,7 +105,7 @@ fromShelleyBlock blk =
103105
, blkTxs = map fromShelleyTx (getTxs blk)
104106
}
105107

106-
fromMaryBlock :: ShelleyBlock TPraosStandard StandardMary -> Block
108+
fromMaryBlock :: ShelleyBlock (TPraosStandard StandardCrypto) MaryEra -> Block
107109
fromMaryBlock blk =
108110
Block
109111
{ blkEra = Mary
@@ -120,7 +122,7 @@ fromMaryBlock blk =
120122
, blkTxs = map fromMaryTx (getTxs blk)
121123
}
122124

123-
fromAlonzoBlock :: Bool -> Maybe Prices -> ShelleyBlock TPraosStandard StandardAlonzo -> Block
125+
fromAlonzoBlock :: Bool -> Maybe Prices -> ShelleyBlock (TPraosStandard StandardCrypto) AlonzoEra -> Block
124126
fromAlonzoBlock iope mprices blk =
125127
Block
126128
{ blkEra = Alonzo
@@ -137,7 +139,7 @@ fromAlonzoBlock iope mprices blk =
137139
, blkTxs = map (fromAlonzoTx iope mprices) (getTxs blk)
138140
}
139141

140-
fromBabbageBlock :: Bool -> Maybe Prices -> ShelleyBlock PraosStandard StandardBabbage -> Block
142+
fromBabbageBlock :: Bool -> Maybe Prices -> ShelleyBlock (PraosStandard StandardCrypto) BabbageEra -> Block
141143
fromBabbageBlock iope mprices blk =
142144
Block
143145
{ blkEra = Babbage
@@ -154,7 +156,7 @@ fromBabbageBlock iope mprices blk =
154156
, blkTxs = map (fromBabbageTx iope mprices) (getTxs blk)
155157
}
156158

157-
fromConwayBlock :: Bool -> Maybe Prices -> ShelleyBlock PraosStandard StandardConway -> Block
159+
fromConwayBlock :: Bool -> Maybe Prices -> ShelleyBlock (PraosStandard StandardCrypto) ConwayEra -> Block
158160
fromConwayBlock iope mprices blk =
159161
Block
160162
{ blkEra = Conway
@@ -173,8 +175,8 @@ fromConwayBlock iope mprices blk =
173175

174176
-- -------------------------------------------------------------------------------------------------
175177

176-
getTxs :: forall p era. EraSegWits era => ShelleyBlock p era -> [(Word64, Ledger.Tx era)]
177-
getTxs = zip [0 ..] . toList . fromTxSeq @era . Ledger.bbody . Consensus.shelleyBlockRaw
178+
getTxs :: forall p era. Ledger.EraSegWits era => ShelleyBlock p era -> [(Word64, Ledger.Tx era)]
179+
getTxs = zip [0 ..] . toList . Ledger.fromTxSeq @era . Ledger.bbody . Consensus.shelleyBlockRaw
178180

179181
blockHeader :: ShelleyBlock p era -> ShelleyProtocolHeader p
180182
blockHeader = Ledger.bheader . Consensus.shelleyBlockRaw
@@ -188,34 +190,34 @@ blockHash =
188190
blockNumber :: ShelleyProtocol p => ShelleyBlock p era -> BlockNo
189191
blockNumber = pHeaderBlock . blockHeader
190192

191-
blockPrevHash :: (ProtoCrypto p ~ StandardCrypto, ProtocolHeaderSupportsEnvelope p) => ShelleyBlock p era -> Maybe ByteString
193+
blockPrevHash :: ProtocolHeaderSupportsEnvelope p => ShelleyBlock p era -> Maybe ByteString
192194
blockPrevHash blk =
193195
case pHeaderPrevHash $ Ledger.bheader (Consensus.shelleyBlockRaw blk) of
194196
TPraos.GenesisHash -> Nothing
195197
TPraos.BlockHash (TPraos.HashHeader h) -> Just $ Crypto.hashToBytes h
196198

197-
blockOpCertKeyTPraos :: ShelleyBlock TPraosStandard era -> ByteString
199+
blockOpCertKeyTPraos :: ShelleyBlock (TPraosStandard StandardCrypto) era -> ByteString
198200
blockOpCertKeyTPraos = KES.rawSerialiseVerKeyKES . TPraos.ocertVkHot . blockOpCertTPraos
199201

200-
blockOpCertKeyPraos :: ShelleyBlock PraosStandard era -> ByteString
202+
blockOpCertKeyPraos :: ShelleyBlock (PraosStandard StandardCrypto) era -> ByteString
201203
blockOpCertKeyPraos = KES.rawSerialiseVerKeyKES . TPraos.ocertVkHot . blockOpCertPraos
202204

203-
blockOpCertCounterTPraos :: ShelleyBlock TPraosStandard era -> Word64
205+
blockOpCertCounterTPraos :: ShelleyBlock (TPraosStandard StandardCrypto) era -> Word64
204206
blockOpCertCounterTPraos = TPraos.ocertN . blockOpCertTPraos
205207

206-
blockOpCertCounterPraos :: ShelleyBlock PraosStandard era -> Word64
208+
blockOpCertCounterPraos :: ShelleyBlock (PraosStandard StandardCrypto) era -> Word64
207209
blockOpCertCounterPraos = TPraos.ocertN . blockOpCertPraos
208210

209-
blockOpCertTPraos :: ShelleyBlock TPraosStandard era -> TPraos.OCert StandardCrypto
211+
blockOpCertTPraos :: ShelleyBlock (TPraosStandard StandardCrypto) era -> TPraos.OCert StandardCrypto
210212
blockOpCertTPraos = TPraos.bheaderOCert . TPraos.bhbody . blockHeader
211213

212-
blockOpCertPraos :: ShelleyBlock PraosStandard era -> TPraos.OCert StandardCrypto
214+
blockOpCertPraos :: ShelleyBlock (PraosStandard StandardCrypto) era -> TPraos.OCert StandardCrypto
213215
blockOpCertPraos = Praos.hbOCert . getHeaderBodyPraos . blockHeader
214216

215-
blockProtoVersionTPraos :: ShelleyBlock TPraosStandard era -> Ledger.ProtVer
217+
blockProtoVersionTPraos :: ShelleyBlock (TPraosStandard StandardCrypto) era -> Ledger.ProtVer
216218
blockProtoVersionTPraos = TPraos.bprotver . TPraos.bhbody . blockHeader
217219

218-
blockProtoVersionPraos :: ShelleyBlock PraosStandard era -> Ledger.ProtVer
220+
blockProtoVersionPraos :: ShelleyBlock (PraosStandard StandardCrypto) era -> Ledger.ProtVer
219221
blockProtoVersionPraos = Praos.hbProtVer . getHeaderBodyPraos . blockHeader
220222

221223
blockSize :: ProtocolHeaderSupportsEnvelope p => ShelleyBlock p era -> Word64
@@ -224,19 +226,19 @@ blockSize = fromIntegral . pHeaderBlockSize . blockHeader
224226
blockVrfKeyView :: VerKeyVRF (VRF StandardCrypto) -> Text
225227
blockVrfKeyView = serialiseVerKeyVrfToBech32
226228

227-
blockVrfVkTPraos :: ShelleyBlock TPraosStandard era -> VerKeyVRF StandardCrypto
229+
blockVrfVkTPraos :: ShelleyBlock (TPraosStandard StandardCrypto) era -> VerKeyVRF PraosVRF
228230
blockVrfVkTPraos = TPraos.bheaderVrfVk . TPraos.bhbody . blockHeader
229231

230-
blockVrfVkPraos :: ShelleyBlock PraosStandard era -> VerKeyVRF StandardCrypto
232+
blockVrfVkPraos :: ShelleyBlock (Praos StandardCrypto) era -> VerKeyVRF (VRF StandardCrypto)
231233
blockVrfVkPraos = Praos.hbVrfVk . getHeaderBodyPraos . blockHeader
232234

233235
getHeaderBodyPraos :: Crypto c => Praos.Header c -> Praos.HeaderBody c
234236
getHeaderBodyPraos (Praos.Header headerBody _) = headerBody
235237

236238
blockIssuer ::
237-
(ShelleyProtocol p, Crypto (ProtoCrypto p), ProtoCrypto p ~ crypto) =>
239+
ShelleyProtocol p =>
238240
ShelleyBlock p era ->
239-
KeyHash 'BlockIssuer crypto
241+
KeyHash 'BlockIssuer
240242
blockIssuer = hashKey . pHeaderIssuer . blockHeader
241243

242244
slotNumber :: ShelleyProtocol p => ShelleyBlock p era -> SlotNo

cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/EpochUpdate.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ import qualified Cardano.Protocol.TPraos.API as Shelley
1818
import qualified Cardano.Protocol.TPraos.Rules.Tickn as Shelley
1919
import Cardano.Slotting.Slot (EpochNo (..))
2020
import Data.Strict.Maybe (Maybe (..))
21-
import Ouroboros.Consensus.Cardano.Block (HardForkState (..), StandardConway)
21+
import Ouroboros.Consensus.Cardano.Block (ConwayEra, HardForkState (..))
2222
import Ouroboros.Consensus.Cardano.CanHardFork ()
2323
import qualified Ouroboros.Consensus.HeaderValidation as Consensus
2424
import Ouroboros.Consensus.Ledger.Extended (ExtLedgerState (..))
@@ -30,8 +30,8 @@ data NewEpoch = NewEpoch
3030
, neIsEBB :: !Bool
3131
, neAdaPots :: !(Maybe Shelley.AdaPots)
3232
, neEpochUpdate :: !EpochUpdate
33-
, neDRepState :: !(Maybe (DRepPulsingState StandardConway))
34-
, neEnacted :: !(Maybe (ConwayGovState StandardConway))
33+
, neDRepState :: !(Maybe (DRepPulsingState ConwayEra))
34+
, neEnacted :: !(Maybe (ConwayGovState ConwayEra))
3535
, nePoolDistr :: !(Maybe (Map PoolKeyHash (Coin, Word64), Map PoolKeyHash Natural))
3636
}
3737

@@ -60,9 +60,9 @@ extractEpochNonce extLedgerState =
6060
ChainDepStateBabbage st -> extractNoncePraos st
6161
ChainDepStateConway st -> extractNoncePraos st
6262
where
63-
extractNonce :: Consensus.TPraosState c -> Ledger.Nonce
63+
extractNonce :: Consensus.TPraosState -> Ledger.Nonce
6464
extractNonce =
6565
Shelley.ticknStateEpochNonce . Shelley.csTickn . Consensus.tpraosStateChainDepState
6666

67-
extractNoncePraos :: Consensus.PraosState c -> Ledger.Nonce
67+
extractNoncePraos :: Consensus.PraosState -> Ledger.Nonce
6868
extractNoncePraos = praosStateEpochNonce

cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/ParamProposal.hs

Lines changed: 12 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -20,15 +20,14 @@ import qualified Cardano.Ledger.BaseTypes as Ledger
2020
import Cardano.Ledger.Coin (Coin, unCoin)
2121
import Cardano.Ledger.Conway.Core
2222
import Cardano.Ledger.Conway.PParams (ppuMinFeeRefScriptCostPerByteL)
23-
import Cardano.Ledger.Crypto
2423
import qualified Cardano.Ledger.Keys as Ledger
2524
import Cardano.Ledger.Plutus.Language (Language)
2625
import qualified Cardano.Ledger.Shelley.PParams as Shelley
2726
import Cardano.Prelude
2827
import Cardano.Slotting.Slot (EpochNo (..))
2928
import qualified Data.Map.Strict as Map
3029
import Lens.Micro ((^.))
31-
import Ouroboros.Consensus.Cardano.Block (StandardAlonzo, StandardBabbage, StandardConway)
30+
import Ouroboros.Consensus.Cardano.Block (AlonzoEra, BabbageEra, ConwayEra)
3231

3332
data ParamProposal = ParamProposal
3433
{ pppEpochNo :: !(Maybe EpochNo)
@@ -74,7 +73,7 @@ data ParamProposal = ParamProposal
7473
, pppMinFeeRefScriptCostPerByte :: !(Maybe Rational)
7574
}
7675

77-
convertParamProposal :: EraCrypto era ~ StandardCrypto => Witness era -> Shelley.Update era -> [ParamProposal]
76+
convertParamProposal :: Witness era -> Shelley.Update era -> [ParamProposal]
7877
convertParamProposal witness (Shelley.Update pp epoch) =
7978
case witness of
8079
Shelley {} -> shelleyParamProposal epoch pp
@@ -89,17 +88,17 @@ shelleyParamProposal :: (EraPParams era, ProtVerAtMost era 4, ProtVerAtMost era
8988
shelleyParamProposal epochNo (Shelley.ProposedPPUpdates umap) =
9089
map (convertShelleyParamProposal epochNo) $ Map.toList umap
9190

92-
alonzoParamProposal :: EpochNo -> Shelley.ProposedPPUpdates StandardAlonzo -> [ParamProposal]
91+
alonzoParamProposal :: EpochNo -> Shelley.ProposedPPUpdates AlonzoEra -> [ParamProposal]
9392
alonzoParamProposal epochNo (Shelley.ProposedPPUpdates umap) =
9493
map (convertAlonzoParamProposal epochNo) $ Map.toList umap
9594

96-
babbageParamProposal :: EpochNo -> Shelley.ProposedPPUpdates StandardBabbage -> [ParamProposal]
95+
babbageParamProposal :: EpochNo -> Shelley.ProposedPPUpdates BabbageEra -> [ParamProposal]
9796
babbageParamProposal epochNo (Shelley.ProposedPPUpdates umap) =
9897
map (convertBabbageParamProposal epochNo) $ Map.toList umap
9998

10099
-- -------------------------------------------------------------------------------------------------
101100

102-
convertConwayParamProposal :: PParamsUpdate StandardConway -> ParamProposal
101+
convertConwayParamProposal :: PParamsUpdate ConwayEra -> ParamProposal
103102
convertConwayParamProposal pmap =
104103
ParamProposal
105104
{ pppEpochNo = Nothing
@@ -112,7 +111,7 @@ convertConwayParamProposal pmap =
112111
, pppKeyDeposit = strictMaybeToMaybe (pmap ^. ppuKeyDepositL)
113112
, pppPoolDeposit = strictMaybeToMaybe (pmap ^. ppuPoolDepositL)
114113
, pppMaxEpoch = strictMaybeToMaybe (pmap ^. ppuEMaxL)
115-
, pppOptimalPoolCount = strictMaybeToMaybe (pmap ^. ppuNOptL)
114+
, pppOptimalPoolCount = fromIntegral <$> strictMaybeToMaybe (pmap ^. ppuNOptL)
116115
, pppInfluence = Ledger.unboundRational <$> strictMaybeToMaybe (pmap ^. ppuA0L)
117116
, pppMonetaryExpandRate = strictMaybeToMaybe (pmap ^. ppuRhoL)
118117
, pppTreasuryGrowthRate = strictMaybeToMaybe (pmap ^. ppuTauL)
@@ -144,7 +143,7 @@ convertConwayParamProposal pmap =
144143
, pppMinFeeRefScriptCostPerByte = Ledger.unboundRational <$> strictMaybeToMaybe (pmap ^. ppuMinFeeRefScriptCostPerByteL)
145144
}
146145

147-
convertBabbageParamProposal :: EpochNo -> (Ledger.KeyHash genesis StandardCrypto, PParamsUpdate StandardBabbage) -> ParamProposal
146+
convertBabbageParamProposal :: EpochNo -> (Ledger.KeyHash genesis, PParamsUpdate BabbageEra) -> ParamProposal
148147
convertBabbageParamProposal epochNo (key, pmap) =
149148
ParamProposal
150149
{ pppEpochNo = Just epochNo
@@ -157,7 +156,7 @@ convertBabbageParamProposal epochNo (key, pmap) =
157156
, pppKeyDeposit = strictMaybeToMaybe (pmap ^. ppuKeyDepositL)
158157
, pppPoolDeposit = strictMaybeToMaybe (pmap ^. ppuPoolDepositL)
159158
, pppMaxEpoch = strictMaybeToMaybe (pmap ^. ppuEMaxL)
160-
, pppOptimalPoolCount = strictMaybeToMaybe (pmap ^. ppuNOptL)
159+
, pppOptimalPoolCount = fromIntegral <$> strictMaybeToMaybe (pmap ^. ppuNOptL)
161160
, pppInfluence = Ledger.unboundRational <$> strictMaybeToMaybe (pmap ^. ppuA0L)
162161
, pppMonetaryExpandRate = strictMaybeToMaybe (pmap ^. ppuRhoL)
163162
, pppTreasuryGrowthRate = strictMaybeToMaybe (pmap ^. ppuTauL)
@@ -188,7 +187,7 @@ convertBabbageParamProposal epochNo (key, pmap) =
188187
, pppMinFeeRefScriptCostPerByte = Nothing
189188
}
190189

191-
convertAlonzoParamProposal :: EpochNo -> (Ledger.KeyHash genesis crypto, PParamsUpdate StandardAlonzo) -> ParamProposal
190+
convertAlonzoParamProposal :: EpochNo -> (Ledger.KeyHash genesis, PParamsUpdate AlonzoEra) -> ParamProposal
192191
convertAlonzoParamProposal epochNo (key, pmap) =
193192
ParamProposal
194193
{ pppEpochNo = Just epochNo
@@ -201,7 +200,7 @@ convertAlonzoParamProposal epochNo (key, pmap) =
201200
, pppKeyDeposit = strictMaybeToMaybe (pmap ^. ppuKeyDepositL)
202201
, pppPoolDeposit = strictMaybeToMaybe (pmap ^. ppuPoolDepositL)
203202
, pppMaxEpoch = strictMaybeToMaybe (pmap ^. ppuEMaxL)
204-
, pppOptimalPoolCount = strictMaybeToMaybe (pmap ^. ppuNOptL)
203+
, pppOptimalPoolCount = fromIntegral <$> strictMaybeToMaybe (pmap ^. ppuNOptL)
205204
, pppInfluence = Ledger.unboundRational <$> strictMaybeToMaybe (pmap ^. ppuA0L)
206205
, pppMonetaryExpandRate = strictMaybeToMaybe (pmap ^. ppuRhoL)
207206
, pppTreasuryGrowthRate = strictMaybeToMaybe (pmap ^. ppuTauL)
@@ -234,7 +233,7 @@ convertAlonzoParamProposal epochNo (key, pmap) =
234233
}
235234

236235
-- | This works fine from Shelley to Mary. Not for Alonzo since 'ppuMinUTxOValueL' was removed
237-
convertShelleyParamProposal :: (EraPParams era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => EpochNo -> (Ledger.KeyHash genesis crypto, PParamsUpdate era) -> ParamProposal
236+
convertShelleyParamProposal :: (EraPParams era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => EpochNo -> (Ledger.KeyHash genesis, PParamsUpdate era) -> ParamProposal
238237
convertShelleyParamProposal epochNo (key, pmap) =
239238
ParamProposal
240239
{ pppEpochNo = Just epochNo
@@ -247,7 +246,7 @@ convertShelleyParamProposal epochNo (key, pmap) =
247246
, pppKeyDeposit = strictMaybeToMaybe (pmap ^. ppuKeyDepositL)
248247
, pppPoolDeposit = strictMaybeToMaybe (pmap ^. ppuPoolDepositL)
249248
, pppMaxEpoch = strictMaybeToMaybe (pmap ^. ppuEMaxL)
250-
, pppOptimalPoolCount = strictMaybeToMaybe (pmap ^. ppuNOptL)
249+
, pppOptimalPoolCount = fromIntegral <$> strictMaybeToMaybe (pmap ^. ppuNOptL)
251250
, pppInfluence = Ledger.unboundRational <$> strictMaybeToMaybe (pmap ^. ppuA0L)
252251
, pppMonetaryExpandRate = strictMaybeToMaybe (pmap ^. ppuRhoL)
253252
, pppTreasuryGrowthRate = strictMaybeToMaybe (pmap ^. ppuTauL)

cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/Tx/Allegra.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -45,9 +45,9 @@ import qualified Data.Aeson as Aeson
4545
import qualified Data.ByteString.Lazy.Char8 as LBS
4646
import qualified Data.Map.Strict as Map
4747
import Lens.Micro ((^.))
48-
import Ouroboros.Consensus.Cardano.Block (StandardAllegra, StandardCrypto)
48+
import Ouroboros.Consensus.Cardano.Block (AllegraEra)
4949

50-
fromAllegraTx :: (Word64, Core.Tx StandardAllegra) -> Tx
50+
fromAllegraTx :: (Word64, Core.Tx AllegraEra) -> Tx
5151
fromAllegraTx (blkIndex, tx) =
5252
Tx
5353
{ txHash = txHashId tx
@@ -81,7 +81,7 @@ fromAllegraTx (blkIndex, tx) =
8181
, txTreasuryDonation = mempty -- Allegra does not support treasury donations
8282
}
8383
where
84-
txBody :: Core.TxBody StandardAllegra
84+
txBody :: Core.TxBody AllegraEra
8585
txBody = tx ^. Core.bodyTxL
8686

8787
outputs :: [TxOut]
@@ -94,7 +94,7 @@ fromAllegraTx (blkIndex, tx) =
9494

9595
getScripts ::
9696
forall era.
97-
(EraCrypto era ~ StandardCrypto, NativeScript era ~ Timelock era, AllegraEraScript era, Core.Tx era ~ ShelleyTx era, TxAuxData era ~ AllegraTxAuxData era, Script era ~ Timelock era, EraTx era) =>
97+
(NativeScript era ~ Timelock era, AllegraEraScript era, Core.Tx era ~ ShelleyTx era, TxAuxData era ~ AllegraTxAuxData era, Script era ~ Timelock era, EraTx era) =>
9898
ShelleyTx era ->
9999
[TxScript]
100100
getScripts tx =
@@ -105,9 +105,9 @@ getScripts tx =
105105

106106
getAuxScripts ::
107107
forall era.
108-
(EraCrypto era ~ StandardCrypto, EraScript era, Script era ~ Timelock era) =>
108+
(EraScript era, Script era ~ Timelock era) =>
109109
StrictMaybe (AllegraTxAuxData era) ->
110-
[(ScriptHash StandardCrypto, Timelock era)]
110+
[(ScriptHash, Timelock era)]
111111
getAuxScripts maux =
112112
case strictMaybeToMaybe maux of
113113
Nothing -> []
@@ -116,7 +116,7 @@ getAuxScripts maux =
116116

117117
mkTxScript ::
118118
(NativeScript era ~ Timelock era, AllegraEraScript era) =>
119-
(ScriptHash StandardCrypto, Timelock era) ->
119+
(ScriptHash, Timelock era) ->
120120
TxScript
121121
mkTxScript (hsh, script) =
122122
TxScript

0 commit comments

Comments
 (0)