@@ -4,13 +4,13 @@ module CardanoNode where
4
4
5
5
import Hydra.Prelude
6
6
7
- import Control.Lens ((^?!) )
7
+ import Control.Lens ((?~) , ( ^?!) )
8
8
import Control.Tracer (Tracer , traceWith )
9
- import Data.Aeson ((.=) )
9
+ import Data.Aeson (Value ( String ), (.=) )
10
10
import Data.Aeson qualified as Aeson
11
- import Data.Aeson.KeyMap qualified as Aeson.KeyMap
12
- import Data.Aeson.Lens (key , _Number )
11
+ import Data.Aeson.Lens (atKey , key , _Number )
13
12
import Data.Fixed (Centi )
13
+ import Data.Text qualified as Text
14
14
import Data.Time.Clock.POSIX (posixSecondsToUTCTime , utcTimeToPOSIXSeconds )
15
15
import Hydra.Cardano.Api (AsType (AsPaymentKey ), File (.. ), NetworkId , PaymentKey , SigningKey , SocketPath , VerificationKey , generateSigningKey , getVerificationKey )
16
16
import Hydra.Cardano.Api qualified as Api
@@ -77,7 +77,7 @@ defaultCardanoNodeArgs :: CardanoNodeArgs
77
77
defaultCardanoNodeArgs =
78
78
CardanoNodeArgs
79
79
{ nodeSocket = " node.socket"
80
- , nodeConfigFile = " configuration .json"
80
+ , nodeConfigFile = " cardano-node .json"
81
81
, nodeByronGenesisFile = " genesis-byron.json"
82
82
, nodeShelleyGenesisFile = " genesis-shelley.json"
83
83
, nodeAlonzoGenesisFile = " genesis-alonzo.json"
@@ -117,64 +117,14 @@ withCardanoNodeDevnet ::
117
117
(RunningNode -> IO a ) ->
118
118
IO a
119
119
withCardanoNodeDevnet tracer stateDirectory action = do
120
- createDirectoryIfMissing True stateDirectory
121
- [dlgCert, signKey, vrfKey, kesKey, opCert] <-
122
- mapM
123
- copyDevnetCredential
124
- [ " byron-delegation.cert"
125
- , " byron-delegate.key"
126
- , " vrf.skey"
127
- , " kes.skey"
128
- , " opcert.cert"
129
- ]
130
- let args =
131
- defaultCardanoNodeArgs
132
- { nodeDlgCertFile = Just dlgCert
133
- , nodeSignKeyFile = Just signKey
134
- , nodeVrfKeyFile = Just vrfKey
135
- , nodeKesKeyFile = Just kesKey
136
- , nodeOpCertFile = Just opCert
137
- }
138
- copyDevnetFiles args
139
- refreshSystemStart stateDirectory args
140
- writeTopology [] args
141
-
120
+ args <- setupCardanoDevnet stateDirectory
142
121
withCardanoNode tracer networkId stateDirectory args $ \ rn -> do
143
122
traceWith tracer MsgNodeIsReady
144
123
action rn
145
124
where
146
125
-- NOTE: This needs to match what's in config/genesis-shelley.json
147
126
networkId = defaultNetworkId
148
127
149
- copyDevnetCredential file = do
150
- let destination = stateDirectory </> file
151
- unlessM (doesFileExist destination) $
152
- readConfigFile (" devnet" </> file)
153
- >>= writeFileBS destination
154
- setFileMode destination ownerReadMode
155
- pure file
156
-
157
- copyDevnetFiles args = do
158
- readConfigFile (" devnet" </> " cardano-node.json" )
159
- >>= writeFileBS
160
- (stateDirectory </> nodeConfigFile args)
161
- readConfigFile (" devnet" </> " genesis-byron.json" )
162
- >>= writeFileBS
163
- (stateDirectory </> nodeByronGenesisFile args)
164
- readConfigFile (" devnet" </> " genesis-shelley.json" )
165
- >>= writeFileBS
166
- (stateDirectory </> nodeShelleyGenesisFile args)
167
- readConfigFile (" devnet" </> " genesis-alonzo.json" )
168
- >>= writeFileBS
169
- (stateDirectory </> nodeAlonzoGenesisFile args)
170
- readConfigFile (" devnet" </> " genesis-conway.json" )
171
- >>= writeFileBS
172
- (stateDirectory </> nodeConwayGenesisFile args)
173
-
174
- writeTopology peers args =
175
- Aeson. encodeFile (stateDirectory </> nodeTopologyFile args) $
176
- mkTopology peers
177
-
178
128
-- | Run a cardano-node as normal network participant on a known network.
179
129
withCardanoNodeOnKnownNetwork ::
180
130
Tracer IO NodeLog ->
@@ -205,7 +155,7 @@ withCardanoNodeOnKnownNetwork tracer workDir knownNetwork action = do
205
155
readNetworkId = do
206
156
shelleyGenesis :: Aeson. Value <- unsafeDecodeJson =<< readFileBS (workDir </> " shelley-genesis.json" )
207
157
if shelleyGenesis ^?! key " networkId" == " Mainnet"
208
- then pure $ Api. Mainnet
158
+ then pure Api. Mainnet
209
159
else do
210
160
let magic = shelleyGenesis ^?! key " networkMagic" . _Number
211
161
pure $ Api. Testnet (Api. NetworkMagic $ truncate magic)
@@ -241,6 +191,73 @@ withCardanoNodeOnKnownNetwork tracer workDir knownNetwork action = do
241
191
fetchConfigFile path =
242
192
parseRequestThrow path >>= httpBS <&> getResponseBody
243
193
194
+ -- | Setup the cardano-node to run a local devnet producing blocks. This copies
195
+ -- the appropriate files and prepares 'CardanoNodeArgs' for 'withCardanoNode'.
196
+ setupCardanoDevnet :: FilePath -> IO CardanoNodeArgs
197
+ setupCardanoDevnet stateDirectory = do
198
+ createDirectoryIfMissing True stateDirectory
199
+ [dlgCert, signKey, vrfKey, kesKey, opCert] <-
200
+ mapM
201
+ copyDevnetCredential
202
+ [ " byron-delegation.cert"
203
+ , " byron-delegate.key"
204
+ , " vrf.skey"
205
+ , " kes.skey"
206
+ , " opcert.cert"
207
+ ]
208
+ let args =
209
+ defaultCardanoNodeArgs
210
+ { nodeDlgCertFile = Just dlgCert
211
+ , nodeSignKeyFile = Just signKey
212
+ , nodeVrfKeyFile = Just vrfKey
213
+ , nodeKesKeyFile = Just kesKey
214
+ , nodeOpCertFile = Just opCert
215
+ }
216
+ copyDevnetFiles args
217
+ refreshSystemStart stateDirectory args
218
+ writeTopology [] args
219
+ pure args
220
+ where
221
+ copyDevnetCredential file = do
222
+ let destination = stateDirectory </> file
223
+ unlessM (doesFileExist destination) $
224
+ readConfigFile (" devnet" </> file)
225
+ >>= writeFileBS destination
226
+ setFileMode destination ownerReadMode
227
+ pure file
228
+
229
+ copyDevnetFiles args = do
230
+ readConfigFile (" devnet" </> " cardano-node.json" )
231
+ >>= writeFileBS
232
+ (stateDirectory </> nodeConfigFile args)
233
+ readConfigFile (" devnet" </> " genesis-byron.json" )
234
+ >>= writeFileBS
235
+ (stateDirectory </> nodeByronGenesisFile args)
236
+ readConfigFile (" devnet" </> " genesis-shelley.json" )
237
+ >>= writeFileBS
238
+ (stateDirectory </> nodeShelleyGenesisFile args)
239
+ readConfigFile (" devnet" </> " genesis-alonzo.json" )
240
+ >>= writeFileBS
241
+ (stateDirectory </> nodeAlonzoGenesisFile args)
242
+ readConfigFile (" devnet" </> " genesis-conway.json" )
243
+ >>= writeFileBS
244
+ (stateDirectory </> nodeConwayGenesisFile args)
245
+
246
+ writeTopology peers args =
247
+ Aeson. encodeFile (stateDirectory </> nodeTopologyFile args) $
248
+ mkTopology peers
249
+
250
+ -- | Modify the cardano-node configuration to fork into conway at given era
251
+ -- number.
252
+ forkIntoConwayInEpoch :: FilePath -> CardanoNodeArgs -> Natural -> IO ()
253
+ forkIntoConwayInEpoch stateDirectory args n = do
254
+ config <-
255
+ unsafeDecodeJsonFile @ Aeson. Value (stateDirectory </> nodeConfigFile args)
256
+ <&> atKey " TestConwayHardForkAtEpoch" ?~ toJSON n
257
+ Aeson. encodeFile
258
+ (stateDirectory </> nodeConfigFile args)
259
+ config
260
+
244
261
withCardanoNode ::
245
262
Tracer IO NodeLog ->
246
263
NetworkId ->
@@ -341,19 +358,19 @@ refreshSystemStart stateDirectory args = do
341
358
systemStart <- initSystemStart
342
359
let startTime = round @ _ @ Int $ utcTimeToPOSIXSeconds systemStart
343
360
byronGenesis <-
344
- unsafeDecodeJsonFile (stateDirectory </> nodeByronGenesisFile args)
345
- <&> addField " startTime" startTime
361
+ unsafeDecodeJsonFile @ Aeson. Value (stateDirectory </> nodeByronGenesisFile args)
362
+ <&> atKey " startTime" ?~ toJSON startTime
346
363
347
364
let systemStartUTC =
348
365
posixSecondsToUTCTime . fromRational . toRational $ startTime
349
366
shelleyGenesis <-
350
- unsafeDecodeJsonFile (stateDirectory </> nodeShelleyGenesisFile args)
351
- <&> addField " systemStart" systemStartUTC
367
+ unsafeDecodeJsonFile @ Aeson. Value (stateDirectory </> nodeShelleyGenesisFile args)
368
+ <&> atKey " systemStart" ?~ toJSON systemStartUTC
352
369
353
370
config <-
354
- unsafeDecodeJsonFile (stateDirectory </> nodeConfigFile args)
355
- <&> addField " ByronGenesisFile" ( nodeByronGenesisFile args)
356
- <&> addField " ShelleyGenesisFile" ( nodeShelleyGenesisFile args)
371
+ unsafeDecodeJsonFile @ Aeson. Value (stateDirectory </> nodeConfigFile args)
372
+ <&> (atKey " ByronGenesisFile" ?~ toJSON ( Text. pack $ nodeByronGenesisFile args) )
373
+ . (atKey " ShelleyGenesisFile" ?~ String ( Text. pack $ nodeShelleyGenesisFile args) )
357
374
358
375
Aeson. encodeFile
359
376
(stateDirectory </> nodeByronGenesisFile args)
@@ -402,9 +419,6 @@ data NodeLog
402
419
-- Helpers
403
420
--
404
421
405
- addField :: ToJSON a => Aeson. Key -> a -> Aeson. Value -> Aeson. Value
406
- addField k v = withObject (Aeson.KeyMap. insert k (toJSON v))
407
-
408
422
-- | Do something with an a JSON object. Fails if the given JSON value isn't an
409
423
-- object.
410
424
withObject :: (Aeson. Object -> Aeson. Object ) -> Aeson. Value -> Aeson. Value
0 commit comments