Skip to content

Commit d2b36f0

Browse files
committed
Update to node 10.6
1 parent f0630b1 commit d2b36f0

File tree

38 files changed

+368
-153
lines changed

38 files changed

+368
-153
lines changed

cabal.project

Lines changed: 13 additions & 3 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-08-03T21:32:16Z
14-
, cardano-haskell-packages 2025-07-30T14:13:57Z
13+
, hackage.haskell.org 2025-10-17T00:26:22Z
14+
, cardano-haskell-packages 2025-11-07T15:42:47Z
1515

1616
packages:
1717
cardano-db
@@ -75,7 +75,6 @@ constraints:
7575
-- then clashes with the `show` in `Prelude`.
7676
, text < 2.1.2
7777

78-
, cardano-node ^>= 10.4
7978

8079
if impl (ghc >= 9.12)
8180
allow-newer:
@@ -86,3 +85,14 @@ if impl (ghc >= 9.12)
8685
-- when using the "cabal" wrapper script provided by nix-shell.
8786
-- --------------------------- 8< --------------------------
8887
-- Please do not put any `source-repository-package` clause above this line.
88+
89+
source-repository-package
90+
type: git
91+
location: https://github.com/IntersectMBO/cardano-node
92+
tag: f5ac0eb01b56af80e8d430828ff6000b6abb92e9
93+
--sha256: sha256-pm+lbEiRdQesnkaXmzn58aWlBhD29l7QHGNtJiDlzuA=
94+
subdir:
95+
cardano-node
96+
trace-dispatcher
97+
trace-forward
98+
trace-resources

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

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -97,10 +97,9 @@ library
9797
, plutus-ledger-api:{plutus-ledger-api-testlib}
9898
, serialise
9999
, strict-sop-core
100-
, strict-stm
100+
, io-classes:strict-stm
101101
, text
102102
, typed-protocols
103-
, typed-protocols-stateful
104103

105104
test-suite cardano-chain-gen
106105
type: exitcode-stdio-1.0
@@ -161,7 +160,6 @@ test-suite cardano-chain-gen
161160
, async
162161
, base
163162
, bytestring
164-
, cardano-api
165163
, cardano-crypto-class
166164
, cardano-db
167165
, cardano-db-sync
@@ -185,7 +183,6 @@ test-suite cardano-chain-gen
185183
, int-cast
186184
, silently
187185
, stm
188-
, strict-stm
189186
, tasty
190187
, tasty-quickcheck
191188
, text

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

Lines changed: 12 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -51,8 +51,8 @@ import Data.Maybe (fromJust)
5151
import Data.Void (Void)
5252
import qualified Network.Mux as Mux
5353
import Network.TypedProtocol.Peer (Peer (..))
54-
import Network.TypedProtocol.Stateful.Codec ()
55-
import qualified Network.TypedProtocol.Stateful.Peer as St
54+
-- import Network.TypedProtocol.Stateful.Codec ()
55+
-- import qualified Network.TypedProtocol.Stateful.Peer as St
5656
import Ouroboros.Consensus.Block (CodecConfig, HasHeader, Point, StandardHash, castPoint)
5757
import Ouroboros.Consensus.Config (TopLevelConfig, configCodec)
5858
import Ouroboros.Consensus.Ledger.Query (BlockQuery, BlockSupportsLedgerQuery, QueryFootprint (..), ShowQuery)
@@ -92,8 +92,7 @@ import Ouroboros.Network.IOManager (IOManager)
9292
import qualified Ouroboros.Network.IOManager as IOManager
9393
import Ouroboros.Network.Magic (NetworkMagic)
9494
import Ouroboros.Network.Mux (OuroborosApplicationWithMinimalCtx)
95-
import Ouroboros.Network.NodeToClient (NodeToClientVersionData (..))
96-
import qualified Ouroboros.Network.NodeToClient as NodeToClient
95+
import Ouroboros.Network.NodeToClient
9796
import Ouroboros.Network.NodeToNode (Versions)
9897
import Ouroboros.Network.Protocol.ChainSync.Server (
9998
ChainSyncServer (..),
@@ -107,6 +106,7 @@ import qualified Ouroboros.Network.Protocol.LocalStateQuery.Type as LocalStateQu
107106
import Ouroboros.Network.Snocket (LocalAddress, LocalSnocket, LocalSocket (..))
108107
import qualified Ouroboros.Network.Snocket as Snocket
109108
import Ouroboros.Network.Util.ShowProxy (Proxy (..), ShowProxy (..))
109+
import Ouroboros.Network.Socket
110110

111111
{- HLINT ignore "Use readTVarIO" -}
112112

@@ -213,16 +213,16 @@ runLocalServer ::
213213
StrictTVar IO (ChainProducerState blk) ->
214214
IO ()
215215
runLocalServer iom codecConfig netMagic localDomainSock chainProdState =
216+
withSnocket nullTracer noAttenuation Map.empty $ \localSocket localSnocket -> do
217+
216218
withSnocket iom localDomainSock $ \localSocket localSnocket -> do
217-
networkState <- NodeToClient.newNetworkMutableState
218219
_ <-
219-
NodeToClient.withServer
220+
runServer
220221
localSnocket
221-
NodeToClient.nullNetworkServerTracers -- debuggingNetworkServerTracers
222-
networkState
222+
nullNetworkConnectTracers -- debuggingNetworkServerTracers
223223
localSocket
224224
(versions chainProdState)
225-
NodeToClient.networkErrorPolicies
225+
networkErrorPolicies
226226
pure ()
227227
where
228228
versions ::
@@ -263,8 +263,7 @@ runLocalServer iom codecConfig netMagic localDomainSock chainProdState =
263263
nullTracer -- TODO add a tracer!
264264
(cChainSyncCodec codecs)
265265
channel
266-
$ chainSyncServerPeer
267-
$ chainSyncServer state codecConfig blockVersion
266+
(chainSyncServerPeer $ chainSyncServer state codecConfig blockVersion)
268267

269268
txSubmitServer ::
270269
localPeer ->
@@ -282,12 +281,11 @@ runLocalServer iom codecConfig netMagic localDomainSock chainProdState =
282281
Channel IO ByteString ->
283282
IO ((), Maybe ByteString)
284283
stateQueryServer _them channel =
285-
St.runPeer
284+
runPeer
286285
nullTracer
287286
(cStateQueryCodec codecs)
288287
channel
289-
LocalStateQuery.StateIdle
290-
(St.Effect (forever $ threadDelay 3_600_000_000))
288+
(LocalStateQuery.StateIdle (Effect (forever $ threadDelay 3_600_000_000)))
291289

292290
txMonitorServer ::
293291
localPeer ->

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

Lines changed: 7 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -138,17 +138,16 @@ resolveStakeCreds indx st = case indx of
138138
rewardAccs =
139139
Map.toList $
140140
UMap.rewardMap $
141-
dsUnified dstate
141+
dsAccounts dstate
142142

143143
poolParams :: Map (KeyHash 'StakePool) PoolParams
144144
poolParams =
145-
psStakePoolParams $
146145
let certState =
147146
lsCertState $
148147
esLState $
149148
nesEs $
150149
Consensus.shelleyLedgerState st
151-
in certState ^. certPStateL
150+
in certState ^. certPStateL . psStakePoolsL
152151

153152
delegs = UMap.sPoolMap $ dsUnified dstate
154153

@@ -185,28 +184,26 @@ resolvePool pix st = case pix of
185184
PoolIndexNew n -> unregisteredPools !! n
186185
where
187186
poolParams =
188-
Map.elems $
189-
psStakePoolParams $
190187
let certState =
191188
lsCertState $
192189
esLState $
193190
nesEs $
194191
Consensus.shelleyLedgerState st
195-
in certState ^. certPStateL
192+
in Map.elems (certState ^. certPStateL . psStakePoolsL)
196193

197194
allPoolStakeCert :: EraCertState era => LedgerState (ShelleyBlock p era) mk -> [ShelleyTxCert era]
198195
allPoolStakeCert st =
199196
ShelleyTxCertDelegCert . ShelleyRegCert <$> nub creds
200197
where
198+
poolParms :: Int
201199
poolParms =
202-
Map.elems $
203-
psStakePoolParams $
204-
let certState =
200+
let certState :: Int
201+
certState =
205202
lsCertState $
206203
esLState $
207204
nesEs $
208205
Consensus.shelleyLedgerState st
209-
in certState ^. certPStateL
206+
in Map.elems (certState ^. certPStateL . psStakePoolsL)
210207
creds = concatMap getPoolStakeCreds poolParms
211208

212209
getPoolStakeCreds :: PoolParams -> [StakeCredential]

cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -255,8 +255,9 @@ mkConfig staticDir mutableDir cmdLineArgs config = do
255255
genCfg <- runOrThrowIO $ runExceptT (readCardanoGenesisConfig config)
256256
let (pInfoDbSync, _) = mkProtocolInfoCardano genCfg []
257257
creds <- mkShelleyCredentials $ cfgDir </> "pools" </> "bulk1.creds"
258-
let (pInfoForger, forging) = mkProtocolInfoCardano genCfg creds
259-
forging' <- forging
258+
let (pInfoForger, mkForgings) = mkProtocolInfoCardano genCfg creds
259+
forgings <- mkForgings
260+
forgings' <- mapM mkBlockForging forgings
260261
syncPars <- mkSyncNodeParams staticDir mutableDir cmdLineArgs
261262
pure $ Config (Consensus.pInfoConfig pInfoDbSync) pInfoDbSync pInfoForger forging' syncPars
262263

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

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -77,6 +77,7 @@ library
7777
Cardano.DbSync.Era.Shelley.Generic.Tx.Alonzo
7878
Cardano.DbSync.Era.Shelley.Generic.Tx.Babbage
7979
Cardano.DbSync.Era.Shelley.Generic.Tx.Conway
80+
Cardano.DbSync.Era.Shelley.Generic.Tx.Dijkstra
8081
Cardano.DbSync.Era.Shelley.Generic.Tx.Mary
8182
Cardano.DbSync.Era.Shelley.Generic.Tx.Shelley
8283
Cardano.DbSync.Era.Shelley.Generic.Tx.Types
@@ -162,6 +163,7 @@ library
162163
, cardano-ledger-core
163164
, cardano-ledger-conway >= 1.17.3
164165
, cardano-ledger-binary
166+
, cardano-ledger-dijkstra
165167
, cardano-ledger-mary
166168
, cardano-ledger-shelley >= 1.12.3.0
167169
, cardano-node
@@ -205,10 +207,10 @@ library
205207
, small-steps
206208
, stm
207209
, strict
210+
, io-classes:strict-stm
208211
, sop-core
209212
, sop-extras
210213
, strict-sop-core
211-
, strict-stm
212214
, swagger2
213215
, text
214216
, time

cardano-db-sync/src/Cardano/DbSync/Api/Ledger.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -80,6 +80,7 @@ storeUTxOFromLedger ::
8080
storeUTxOFromLedger env st = case ledgerState st of
8181
LedgerStateBabbage bts -> storeUTxO env (getUTxO bts)
8282
LedgerStateConway stc -> storeUTxO env (getUTxO stc)
83+
LedgerStateDijkstra stc -> storeUTxO env (getUTxO stc)
8384
_otherwise -> liftIO $ logError trce "storeUTxOFromLedger is only supported after Babbage"
8485
where
8586
trce = getTrace env

cardano-db-sync/src/Cardano/DbSync/Config/Cardano.hs

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,9 @@ import Ouroboros.Consensus.Config (TopLevelConfig (..), emptyCheckpointsMap)
3838
import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo)
3939
import qualified Ouroboros.Consensus.Node.ProtocolInfo as Consensus
4040
import Ouroboros.Consensus.Shelley.Node (ShelleyGenesis (..))
41+
import Cardano.Node.Protocol.Dijkstra
42+
import Control.Tracer (nullTracer)
43+
import Cardano.Prelude (second)
4144

4245
-- Usually only one constructor, but may have two when we are preparing for a HFC event.
4346
data GenesisConfig
@@ -82,8 +85,8 @@ mkTopLevelConfig cfg = Consensus.pInfoConfig $ fst $ mkProtocolInfoCardano cfg [
8285
mkProtocolInfoCardano ::
8386
GenesisConfig ->
8487
[Consensus.ShelleyLeaderCredentials StandardCrypto] -> -- this is not empty only in tests
85-
(ProtocolInfo CardanoBlock, IO [BlockForging IO CardanoBlock])
86-
mkProtocolInfoCardano genesisConfig shelleyCred =
88+
(ProtocolInfo CardanoBlock, IO [MkBlockForging IO CardanoBlock])
89+
mkProtocolInfoCardano genesisConfig shelleyCred = second (\f -> f nullTracer) $
8790
protocolInfoCardano $
8891
CardanoProtocolParams
8992
{ byronProtocolParams =
@@ -105,6 +108,7 @@ mkProtocolInfoCardano genesisConfig shelleyCred =
105108
shelleyGenesis
106109
alonzoGenesis
107110
conwayGenesis
111+
emptyDijkstraGenesis -- TODO(Dijkstra)
108112
, cardanoHardForkTriggers =
109113
Consensus.CardanoHardForkTriggers'
110114
{ triggerHardForkShelley = dncShelleyHardFork dnc
@@ -113,6 +117,7 @@ mkProtocolInfoCardano genesisConfig shelleyCred =
113117
, triggerHardForkAlonzo = dncAlonzoHardFork dnc
114118
, triggerHardForkBabbage = dncBabbageHardFork dnc
115119
, triggerHardForkConway = dncConwayHardFork dnc
120+
, triggerHardForkDijkstra = Consensus.CardanoTriggerHardForkAtDefaultVersion -- TODO(Dijkstra)
116121
}
117122
, cardanoCheckpoints = emptyCheckpointsMap
118123
}

cardano-db-sync/src/Cardano/DbSync/Default.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -197,6 +197,9 @@ insertBlock syncEnv cblk applyRes firstAfterRollback tookSnapshot = do
197197
BlockConway blk ->
198198
insertBlockUniversal' $
199199
Generic.fromConwayBlock (ioPlutusExtra iopts) (getPrices applyResult) blk
200+
BlockDijkstra blk ->
201+
insertBlockUniversal' $
202+
Generic.fromDijkstraBlock (ioPlutusExtra iopts) (getPrices applyResult) blk
200203
-- update the epoch
201204
updateEpoch details isNewEpochEvent
202205
whenPruneTxOut syncEnv $

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ epochHandler syncEnv trce cache isNewEpochEvent (BlockDetails cblk details) =
5555
BlockAlonzo {} -> epochSlotTimecheck
5656
BlockBabbage {} -> epochSlotTimecheck
5757
BlockConway {} -> epochSlotTimecheck
58+
BlockDijkstra {} -> epochSlotTimecheck
5859
where
5960
-- What we do here is completely independent of Shelley/Allegra/Mary eras.
6061
epochSlotTimecheck :: ExceptT SyncNodeError DB.DbM ()

0 commit comments

Comments
 (0)