Skip to content

Commit 8de95e5

Browse files
erikdcoot
andcommitted
Continuation of 'Make it build with ghc-9.12'
Co-Authored-By: Marcin Szamotulski <[email protected]>
1 parent 3fa7c70 commit 8de95e5

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

73 files changed

+755
-743
lines changed

cabal.project

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,8 @@ repository cardano-haskell-packages
1010
d4a35cd3121aa00d18544bb0ac01c3e1691d618f462c46129271bccf39f7e8ee
1111

1212
index-state:
13-
, hackage.haskell.org 2025-04-15T19:49:23Z
14-
, cardano-haskell-packages 2025-04-16T08:24:34Z
13+
, hackage.haskell.org 2025-04-29T21:50:43Z
14+
, cardano-haskell-packages 2025-04-29T20:52:57Z
1515

1616
packages:
1717
cardano-db

cardano-chain-gen/cardano-chain-gen.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,7 @@ library
8585
, extra
8686
, mtl
8787
, microlens
88+
, network-mux
8889
, nothunks
8990
, ouroboros-consensus
9091
, ouroboros-consensus-cardano
@@ -100,7 +101,6 @@ library
100101
, strict-sop-core
101102
, strict-stm
102103
, text
103-
, typed-protocols
104104

105105
test-suite cardano-chain-gen
106106
type: exitcode-stdio-1.0

cardano-chain-gen/src/Cardano/Mock/ChainDB.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ replaceGenesisDB chainDB st = chainDB {cchain = Genesis st}
6262
extendChainDB :: LedgerSupportsProtocol block => ChainDB block -> block -> ChainDB block
6363
extendChainDB chainDB blk = do
6464
let !chain = cchain chainDB
65-
!st = tickThenReapply (Consensus.ExtLedgerCfg $ chainConfig chainDB) blk (getTipState chain)
65+
!st = tickThenReapply ComputeLedgerEvents (Consensus.ExtLedgerCfg $ chainConfig chainDB) blk (getTipState chain)
6666
in chainDB {cchain = chain :> (blk, st)}
6767

6868
findFirstPoint :: HasHeader block => [Point block] -> ChainDB block -> Maybe (Point block)

cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ import Data.ByteString.Lazy.Char8 (ByteString)
4848
import qualified Data.Map.Strict as Map
4949
import Data.Maybe (fromJust)
5050
import Data.Void (Void)
51-
import Network.TypedProtocol.Core (Peer (..))
51+
import qualified Network.Mux as Mux
5252
import Ouroboros.Consensus.Block (CodecConfig, HasHeader, Point, StandardHash, castPoint)
5353
import Ouroboros.Consensus.Config (TopLevelConfig, configCodec)
5454
import Ouroboros.Consensus.Ledger.Query (BlockQuery, ShowQuery)
@@ -86,7 +86,7 @@ import Ouroboros.Network.Driver.Simple (runPeer)
8686
import Ouroboros.Network.IOManager (IOManager)
8787
import qualified Ouroboros.Network.IOManager as IOManager
8888
import Ouroboros.Network.Magic (NetworkMagic)
89-
import Ouroboros.Network.Mux (MuxMode (..), OuroborosApplicationWithMinimalCtx)
89+
import Ouroboros.Network.Mux (OuroborosApplicationWithMinimalCtx)
9090
import Ouroboros.Network.NodeToClient (NodeToClientVersionData (..))
9191
import qualified Ouroboros.Network.NodeToClient as NodeToClient
9292
import Ouroboros.Network.NodeToNode (Versions)
@@ -216,7 +216,7 @@ runLocalServer iom codecConfig netMagic localDomainSock chainProdState =
216216
Versions
217217
NodeToClientVersion
218218
NodeToClientVersionData
219-
(OuroborosApplicationWithMinimalCtx 'ResponderMode LocalAddress ByteString IO Void ())
219+
(OuroborosApplicationWithMinimalCtx 'Mux.ResponderMode LocalAddress ByteString IO Void ())
220220
versions state =
221221
let version = fromJust $ snd $ latestReleasedNodeVersion (Proxy @blk)
222222
allVersions = supportedNodeToClientVersions (Proxy @blk)

cardano-chain-gen/src/Cardano/Mock/Forging/Interpreter.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -75,11 +75,11 @@ import Ouroboros.Consensus.Block (
7575
)
7676
import qualified Ouroboros.Consensus.Block as Block
7777
import Ouroboros.Consensus.Cardano.Block (
78+
AlonzoEra,
79+
BabbageEra,
80+
ConwayEra,
7881
LedgerState (..),
79-
StandardAlonzo,
80-
StandardBabbage,
81-
StandardConway,
82-
StandardShelley,
82+
ShelleyEra,
8383
)
8484
import Ouroboros.Consensus.Cardano.CanHardFork ()
8585
import Ouroboros.Consensus.Config (
@@ -493,7 +493,7 @@ getCurrentSlot interp = istSlot <$> readTVarIO (interpState interp)
493493

494494
withBabbageLedgerState ::
495495
Interpreter ->
496-
(LedgerState (ShelleyBlock PraosStandard StandardBabbage) -> Either ForgingError a) ->
496+
(LedgerState (ShelleyBlock PraosStandard BabbageEra) -> Either ForgingError a) ->
497497
IO a
498498
withBabbageLedgerState inter mk = do
499499
st <- getCurrentLedgerState inter
@@ -505,7 +505,7 @@ withBabbageLedgerState inter mk = do
505505

506506
withConwayLedgerState ::
507507
Interpreter ->
508-
(LedgerState (ShelleyBlock PraosStandard StandardConway) -> Either ForgingError a) ->
508+
(LedgerState (ShelleyBlock PraosStandard ConwayEra) -> Either ForgingError a) ->
509509
IO a
510510
withConwayLedgerState inter mk = do
511511
st <- getCurrentLedgerState inter
@@ -517,7 +517,7 @@ withConwayLedgerState inter mk = do
517517

518518
withAlonzoLedgerState ::
519519
Interpreter ->
520-
(LedgerState (ShelleyBlock TPraosStandard StandardAlonzo) -> Either ForgingError a) ->
520+
(LedgerState (ShelleyBlock TPraosStandard AlonzoEra) -> Either ForgingError a) ->
521521
IO a
522522
withAlonzoLedgerState inter mk = do
523523
st <- getCurrentLedgerState inter
@@ -529,7 +529,7 @@ withAlonzoLedgerState inter mk = do
529529

530530
withShelleyLedgerState ::
531531
Interpreter ->
532-
(LedgerState (ShelleyBlock TPraosStandard StandardShelley) -> Either ForgingError a) ->
532+
(LedgerState (ShelleyBlock TPraosStandard ShelleyEra) -> Either ForgingError a) ->
533533
IO a
534534
withShelleyLedgerState inter mk = do
535535
st <- getCurrentLedgerState inter
@@ -542,10 +542,10 @@ withShelleyLedgerState inter mk = do
542542
mkTxId :: TxEra -> Ledger.TxId StandardCrypto
543543
mkTxId txe =
544544
case txe of
545-
TxAlonzo tx -> txIdTx @StandardAlonzo tx
546-
TxBabbage tx -> txIdTx @StandardBabbage tx
547-
TxConway tx -> txIdTx @StandardConway tx
548-
TxShelley tx -> txIdTx @StandardShelley tx
545+
TxAlonzo tx -> txIdTx @AlonzoEra tx
546+
TxBabbage tx -> txIdTx @BabbageEra tx
547+
TxConway tx -> txIdTx @ConwayEra tx
548+
TxShelley tx -> txIdTx @ShelleyEra tx
549549

550550
mkValidated :: TxEra -> Validated (Consensus.GenTx CardanoBlock)
551551
mkValidated txe =

cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Alonzo.hs

Lines changed: 36 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -63,24 +63,24 @@ import Data.Sequence.Strict (StrictSeq)
6363
import qualified Data.Sequence.Strict as StrictSeq
6464
import qualified Data.Set as Set
6565
import Lens.Micro
66-
import Ouroboros.Consensus.Cardano.Block (LedgerState, StandardAlonzo)
66+
import Ouroboros.Consensus.Cardano.Block (AlonzoEra, LedgerState)
6767
import Ouroboros.Consensus.Shelley.Eras (StandardCrypto)
6868
import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock)
6969
import Prelude hiding (map)
7070

71-
type AlonzoUTxOIndex = UTxOIndex StandardAlonzo
71+
type AlonzoUTxOIndex = UTxOIndex AlonzoEra
7272

73-
type AlonzoLedgerState = LedgerState (ShelleyBlock TPraosStandard StandardAlonzo)
73+
type AlonzoLedgerState = LedgerState (ShelleyBlock TPraosStandard AlonzoEra)
7474

7575
consTxBody ::
7676
Set (TxIn StandardCrypto) ->
7777
Set (TxIn StandardCrypto) ->
78-
StrictSeq (AlonzoTxOut StandardAlonzo) ->
78+
StrictSeq (AlonzoTxOut AlonzoEra) ->
7979
Coin ->
8080
MultiAsset StandardCrypto ->
81-
[ShelleyTxCert StandardAlonzo] ->
81+
[ShelleyTxCert AlonzoEra] ->
8282
Withdrawals StandardCrypto ->
83-
AlonzoTxBody StandardAlonzo
83+
AlonzoTxBody AlonzoEra
8484
consTxBody ins cols outs fees minted certs wdrl =
8585
AlonzoTxBody
8686
ins
@@ -111,13 +111,13 @@ addValidityInterval slotNo tx =
111111
consPaymentTxBody ::
112112
Set (TxIn StandardCrypto) ->
113113
Set (TxIn StandardCrypto) ->
114-
StrictSeq (AlonzoTxOut StandardAlonzo) ->
114+
StrictSeq (AlonzoTxOut AlonzoEra) ->
115115
Coin ->
116116
MultiAsset StandardCrypto ->
117-
AlonzoTxBody StandardAlonzo
117+
AlonzoTxBody AlonzoEra
118118
consPaymentTxBody ins cols outs fees minted = consTxBody ins cols outs fees minted mempty (Withdrawals mempty)
119119

120-
consCertTxBody :: [ShelleyTxCert StandardAlonzo] -> Withdrawals StandardCrypto -> AlonzoTxBody StandardAlonzo
120+
consCertTxBody :: [ShelleyTxCert AlonzoEra] -> Withdrawals StandardCrypto -> AlonzoTxBody AlonzoEra
121121
consCertTxBody = consTxBody mempty mempty mempty (Coin 0) mempty
122122

123123
mkPaymentTx ::
@@ -126,7 +126,7 @@ mkPaymentTx ::
126126
Integer ->
127127
Integer ->
128128
AlonzoLedgerState ->
129-
Either ForgingError (AlonzoTx StandardAlonzo)
129+
Either ForgingError (AlonzoTx AlonzoEra)
130130
mkPaymentTx inputIndex outputIndex amount fees sta = do
131131
(inputPair, _) <- resolveUTxOIndex inputIndex sta
132132
addr <- resolveAddress outputIndex sta
@@ -141,7 +141,7 @@ mkPaymentTx' ::
141141
AlonzoUTxOIndex ->
142142
[(AlonzoUTxOIndex, MaryValue StandardCrypto)] ->
143143
AlonzoLedgerState ->
144-
Either ForgingError (AlonzoTx StandardAlonzo)
144+
Either ForgingError (AlonzoTx AlonzoEra)
145145
mkPaymentTx' inputIndex outputIndex sta = do
146146
inputPair <- fst <$> resolveUTxOIndex inputIndex sta
147147
outps <- mapM mkOuts outputIndex
@@ -162,7 +162,7 @@ mkLockByScriptTx ::
162162
Integer ->
163163
Integer ->
164164
AlonzoLedgerState ->
165-
Either ForgingError (AlonzoTx StandardAlonzo)
165+
Either ForgingError (AlonzoTx AlonzoEra)
166166
mkLockByScriptTx inputIndex spendable amount fees sta = do
167167
(inputPair, _) <- resolveUTxOIndex inputIndex sta
168168

@@ -173,7 +173,7 @@ mkLockByScriptTx inputIndex spendable amount fees sta = do
173173
-- No witnesses are necessary when the outputs is a script address. Only when it's consumed.
174174
Right $ mkSimpleTx True $ consPaymentTxBody input mempty (StrictSeq.fromList $ outs <> [change]) (Coin fees) mempty
175175
where
176-
datahash = hashData @StandardAlonzo plutusDataList
176+
datahash = hashData @AlonzoEra plutusDataList
177177
mkOut sp =
178178
let outAddress = if sp then alwaysSucceedsScriptAddr else alwaysFailsScriptAddr
179179
in AlonzoTxOut outAddress (valueFromList (Coin amount) []) (Strict.SJust datahash)
@@ -186,7 +186,7 @@ mkUnlockScriptTx ::
186186
Integer ->
187187
Integer ->
188188
AlonzoLedgerState ->
189-
Either ForgingError (AlonzoTx StandardAlonzo)
189+
Either ForgingError (AlonzoTx AlonzoEra)
190190
mkUnlockScriptTx inputIndex colInputIndex outputIndex succeeds amount fees sta = do
191191
inputPairs <- fmap fst <$> mapM (`resolveUTxOIndex` sta) inputIndex
192192
(colInputPair, _) <- resolveUTxOIndex colInputIndex sta
@@ -202,13 +202,13 @@ mkUnlockScriptTx inputIndex colInputIndex outputIndex succeeds amount fees sta =
202202
$ consPaymentTxBody inpts colInput (StrictSeq.fromList [output]) (Coin fees) mempty
203203

204204
mkScriptInp' ::
205-
(Word64, (TxIn StandardCrypto, Core.TxOut StandardAlonzo)) ->
206-
Maybe (AlonzoPlutusPurpose AsIx era, Maybe (ScriptHash StandardCrypto, Core.Script StandardAlonzo))
205+
(Word64, (TxIn StandardCrypto, Core.TxOut AlonzoEra)) ->
206+
Maybe (AlonzoPlutusPurpose AsIx era, Maybe (ScriptHash StandardCrypto, Core.Script AlonzoEra))
207207
mkScriptInp' = map (second Just) . mkScriptInp
208208

209209
mkScriptInp ::
210-
(Word64, (TxIn StandardCrypto, Core.TxOut StandardAlonzo)) ->
211-
Maybe (AlonzoPlutusPurpose AsIx era, (ScriptHash StandardCrypto, Core.Script StandardAlonzo))
210+
(Word64, (TxIn StandardCrypto, Core.TxOut AlonzoEra)) ->
211+
Maybe (AlonzoPlutusPurpose AsIx era, (ScriptHash StandardCrypto, Core.Script AlonzoEra))
212212
mkScriptInp (n, (_txIn, txOut))
213213
| addr == alwaysFailsScriptAddr =
214214
Just
@@ -252,7 +252,7 @@ mkMAssetsScriptTx ::
252252
Bool ->
253253
Integer ->
254254
AlonzoLedgerState ->
255-
Either ForgingError (AlonzoTx StandardAlonzo)
255+
Either ForgingError (AlonzoTx AlonzoEra)
256256
mkMAssetsScriptTx inputIndex colInputIndex outputIndex minted succeeds fees sta = do
257257
inputPairs <- fmap fst <$> mapM (`resolveUTxOIndex` sta) inputIndex
258258
colInput <- Set.singleton . fst . fst <$> resolveUTxOIndex colInputIndex sta
@@ -269,18 +269,18 @@ mkMAssetsScriptTx inputIndex colInputIndex outputIndex minted succeeds fees sta
269269
where
270270
mkOuts (outIx, vl) = do
271271
addr <- resolveAddress outIx sta
272-
Right $ AlonzoTxOut addr vl (Strict.SJust (hashData @StandardAlonzo plutusDataList))
272+
Right $ AlonzoTxOut addr vl (Strict.SJust (hashData @AlonzoEra plutusDataList))
273273

274274
mkDCertTx ::
275-
[ShelleyTxCert StandardAlonzo] ->
275+
[ShelleyTxCert AlonzoEra] ->
276276
Withdrawals StandardCrypto ->
277-
Either ForgingError (AlonzoTx StandardAlonzo)
277+
Either ForgingError (AlonzoTx AlonzoEra)
278278
mkDCertTx certs wdrl = Right $ mkSimpleTx True $ consCertTxBody certs wdrl
279279

280280
mkSimpleDCertTx ::
281-
[(StakeIndex, StakeCredential StandardCrypto -> ShelleyTxCert StandardAlonzo)] ->
281+
[(StakeIndex, StakeCredential -> ShelleyTxCert AlonzoEra)] ->
282282
AlonzoLedgerState ->
283-
Either ForgingError (AlonzoTx StandardAlonzo)
283+
Either ForgingError (AlonzoTx AlonzoEra)
284284
mkSimpleDCertTx consDert st = do
285285
dcerts <- forM consDert $ \(stakeIndex, mkDCert) -> do
286286
cred <- resolveStakeCreds stakeIndex st
@@ -290,11 +290,11 @@ mkSimpleDCertTx consDert st = do
290290
mkDCertPoolTx ::
291291
[ ( [StakeIndex]
292292
, PoolIndex
293-
, [StakeCredential StandardCrypto] -> KeyHash 'StakePool StandardCrypto -> ShelleyTxCert StandardAlonzo
293+
, [StakeCredential] -> KeyHash 'StakePool -> ShelleyTxCert AlonzoEra
294294
)
295295
] ->
296296
AlonzoLedgerState ->
297-
Either ForgingError (AlonzoTx StandardAlonzo)
297+
Either ForgingError (AlonzoTx AlonzoEra)
298298
mkDCertPoolTx consDert st = do
299299
dcerts <- forM consDert $ \(stakeIxs, poolIx, mkDCert) -> do
300300
stakeCreds <- forM stakeIxs $ \stix -> resolveStakeCreds stix st
@@ -303,10 +303,10 @@ mkDCertPoolTx consDert st = do
303303
mkDCertTx dcerts (Withdrawals mempty)
304304

305305
mkScriptDCertTx ::
306-
[(StakeIndex, Bool, StakeCredential StandardCrypto -> ShelleyTxCert StandardAlonzo)] ->
306+
[(StakeIndex, Bool, StakeCredential -> ShelleyTxCert AlonzoEra)] ->
307307
Bool ->
308308
AlonzoLedgerState ->
309-
Either ForgingError (AlonzoTx StandardAlonzo)
309+
Either ForgingError (AlonzoTx AlonzoEra)
310310
mkScriptDCertTx consDert valid st = do
311311
dcerts <- forM consDert $ \(stakeIndex, _, mkDCert) -> do
312312
cred <- resolveStakeCreds stakeIndex st
@@ -329,7 +329,7 @@ mkDepositTxPools ::
329329
AlonzoUTxOIndex ->
330330
Integer ->
331331
AlonzoLedgerState ->
332-
Either ForgingError (AlonzoTx StandardAlonzo)
332+
Either ForgingError (AlonzoTx AlonzoEra)
333333
mkDepositTxPools inputIndex deposit sta = do
334334
(inputPair, _) <- resolveUTxOIndex inputIndex sta
335335

@@ -340,10 +340,10 @@ mkDepositTxPools inputIndex deposit sta = do
340340

341341
mkDCertTxPools ::
342342
AlonzoLedgerState ->
343-
Either ForgingError (AlonzoTx StandardAlonzo)
343+
Either ForgingError (AlonzoTx AlonzoEra)
344344
mkDCertTxPools sta = Right $ mkSimpleTx True $ consCertTxBody (allPoolStakeCert sta) (Withdrawals mempty)
345345

346-
mkSimpleTx :: Bool -> AlonzoTxBody StandardAlonzo -> AlonzoTx StandardAlonzo
346+
mkSimpleTx :: Bool -> AlonzoTxBody AlonzoEra -> AlonzoTx AlonzoEra
347347
mkSimpleTx valid txBody =
348348
AlonzoTx
349349
{ body = txBody
@@ -353,9 +353,9 @@ mkSimpleTx valid txBody =
353353
}
354354

355355
consPoolParamsTwoOwners ::
356-
[StakeCredential StandardCrypto] ->
357-
KeyHash 'StakePool StandardCrypto ->
358-
ShelleyTxCert StandardAlonzo
356+
[StakeCredential] ->
357+
KeyHash 'StakePool ->
358+
ShelleyTxCert AlonzoEra
359359
consPoolParamsTwoOwners [rwCred, KeyHashObj owner0, KeyHashObj owner1] poolId =
360360
ShelleyTxCertPool $ RegPool $ consPoolParams poolId rwCred [owner0, owner1]
361361
consPoolParamsTwoOwners _ _ = panic "expected 2 pool owners"
@@ -417,7 +417,7 @@ mkUTxOAlonzo tx =
417417
transId = txIdTx tx
418418
outputsL = Core.bodyTxL . Core.outputsTxBodyL
419419

420-
emptyTxBody :: AlonzoTxBody StandardAlonzo
420+
emptyTxBody :: AlonzoTxBody AlonzoEra
421421
emptyTxBody =
422422
AlonzoTxBody
423423
mempty
@@ -434,7 +434,7 @@ emptyTxBody =
434434
Strict.SNothing
435435
(Strict.SJust Testnet)
436436

437-
emptyTx :: AlonzoTx StandardAlonzo
437+
emptyTx :: AlonzoTx AlonzoEra
438438
emptyTx =
439439
AlonzoTx
440440
{ body = emptyTxBody

0 commit comments

Comments
 (0)