@@ -5,7 +5,7 @@ module Hydra.Model.MockChain where
5
5
import Hydra.Cardano.Api
6
6
import Hydra.Prelude hiding (Any , label )
7
7
8
- import Cardano.Api.UTxO (fromPairs , pairs )
8
+ import Cardano.Api.UTxO (fromPairs )
9
9
import Control.Concurrent.Class.MonadSTM (
10
10
MonadLabelledSTM ,
11
11
MonadSTM (newTVarIO , writeTVar ),
@@ -15,6 +15,7 @@ import Control.Concurrent.Class.MonadSTM (
15
15
newTQueueIO ,
16
16
newTVarIO ,
17
17
readTVarIO ,
18
+ throwSTM ,
18
19
tryReadTQueue ,
19
20
writeTQueue ,
20
21
writeTVar ,
@@ -25,9 +26,11 @@ import Data.Sequence (Seq (Empty, (:|>)))
25
26
import Data.Sequence qualified as Seq
26
27
import Data.Time (secondsToNominalDiffTime )
27
28
import Data.Time.Clock.POSIX (posixSecondsToUTCTime )
29
+ import GHC.IO.Exception (userError )
28
30
import Hydra.BehaviorSpec (
29
31
SimulatedChainNetwork (.. ),
30
32
)
33
+ import Hydra.Cardano.Api.Pretty (renderTxWithUTxO )
31
34
import Hydra.Chain (Chain (.. ), initHistory )
32
35
import Hydra.Chain.Direct.Fixture (testNetworkId )
33
36
import Hydra.Chain.Direct.Handlers (
@@ -52,8 +55,14 @@ import Hydra.HeadLogic (
52
55
Event (.. ),
53
56
defaultTTL ,
54
57
)
55
- import Hydra.HeadLogic.State (ClosedState (.. ), HeadState (.. ), IdleState (.. ), InitialState (.. ), OpenState (.. ))
56
- import Hydra.Ledger (ChainSlot (.. ), Ledger (.. ), txId )
58
+ import Hydra.HeadLogic.State (
59
+ ClosedState (.. ),
60
+ HeadState (.. ),
61
+ IdleState (.. ),
62
+ InitialState (.. ),
63
+ OpenState (.. ),
64
+ )
65
+ import Hydra.Ledger (ChainSlot (.. ), Ledger (.. ), ValidationError (.. ), collectTransactions )
57
66
import Hydra.Ledger.Cardano (adjustUTxO , fromChainSlot , genTxOutAdaOnly )
58
67
import Hydra.Ledger.Cardano.Evaluate (eraHistoryWithoutHorizon , evaluateTx )
59
68
import Hydra.Logging (Tracer )
@@ -92,7 +101,7 @@ mockChainAndNetwork tr seedKeys commits = do
92
101
link tickThread
93
102
pure
94
103
SimulatedChainNetwork
95
- { connectNode = connectNode nodes queue
104
+ { connectNode = connectNode nodes chain queue
96
105
, tickThread
97
106
, rollbackAndForward = rollbackAndForward nodes chain
98
107
, simulateCommit = simulateCommit nodes
@@ -117,7 +126,7 @@ mockChainAndNetwork tr seedKeys commits = do
117
126
let vks = getVerificationKey . signingKey . snd <$> seedKeys
118
127
env{participants = verificationKeyToOnChainId <$> vks}
119
128
120
- connectNode nodes queue node = do
129
+ connectNode nodes chain queue node = do
121
130
localChainState <- newLocalChainState (initHistory initialChainState)
122
131
let Environment {party = ownParty} = env node
123
132
let vkey = fst $ findOwnCardanoKey ownParty seedKeys
@@ -130,12 +139,25 @@ mockChainAndNetwork tr seedKeys commits = do
130
139
}
131
140
let getTimeHandle = pure $ fixedTimeHandleIndefiniteHorizon `generateWith` 42
132
141
let HydraNode {eq = EventQueue {putEvent}} = node
133
- let
134
- -- NOTE: this very simple function put the transaction in a queue for
135
- -- inclusion into the chain. We could want to simulate the local
136
- -- submission of a transaction and the possible failures it introduces,
137
- -- perhaps caused by the node lagging behind
138
- submitTx = atomically . writeTQueue queue
142
+ -- Validate transactions on submission and queue them for inclusion if valid.
143
+ let submitTx tx =
144
+ atomically $ do
145
+ -- NOTE: Determine the current "view" on the chain (important while
146
+ -- rolled back, before new roll forwards were issued)
147
+ (slot, position, blocks, globalUTxO) <- readTVar chain
148
+ let utxo = case Seq. lookup (fromIntegral position) blocks of
149
+ Nothing -> globalUTxO
150
+ Just (_, _, blockUTxO) -> blockUTxO
151
+ case applyTransactions slot utxo [tx] of
152
+ Left (_tx, err) ->
153
+ throwSTM . userError . toString $
154
+ unlines
155
+ [ " MockChain: Invalid tx submitted"
156
+ , " Tx: " <> toText (renderTxWithUTxO utxo tx)
157
+ , " Error: " <> show err
158
+ ]
159
+ Right _utxo' ->
160
+ writeTQueue queue tx
139
161
let chainHandle =
140
162
createMockChain
141
163
tr
@@ -202,12 +224,20 @@ mockChainAndNetwork tr seedKeys commits = do
202
224
(slotNum, position, blocks, _) <- readTVarIO chain
203
225
case Seq. lookup (fromIntegral position) blocks of
204
226
Just (header, txs, utxo) -> do
227
+ let position' = position + 1
205
228
allHandlers <- fmap chainHandler <$> readTVarIO nodes
229
+ -- NOTE: Need to reset the mocked chain ledger to this utxo before
230
+ -- calling the node handlers (as they might submit transactions
231
+ -- directly).
232
+ atomically $ writeTVar chain (slotNum, position', blocks, utxo)
206
233
forM_ allHandlers (\ h -> onRollForward h header txs)
207
- atomically $ writeTVar chain (slotNum, position + 1 , blocks, utxo)
208
234
Nothing ->
209
235
pure ()
210
236
237
+ -- XXX: This should actually work more like a chain fork / switch to longer
238
+ -- chain. That is, the ledger switches to the longer chain state right away
239
+ -- and we issue rollback and forwards to synchronize clients. However,
240
+ -- submission will already validate against the new ledger state.
211
241
rollbackAndForward nodes chain numberOfBlocks = do
212
242
doRollBackward nodes chain numberOfBlocks
213
243
replicateM_ (fromIntegral numberOfBlocks) $
@@ -217,29 +247,25 @@ mockChainAndNetwork tr seedKeys commits = do
217
247
(slotNum, position, blocks, _) <- readTVarIO chain
218
248
case Seq. lookup (fromIntegral $ position - nbBlocks) blocks of
219
249
Just (header, _, utxo) -> do
250
+ let position' = position - nbBlocks + 1
220
251
allHandlers <- fmap chainHandler <$> readTVarIO nodes
221
252
let point = getChainPoint header
253
+ atomically $ writeTVar chain (slotNum, position', blocks, utxo)
222
254
forM_ allHandlers (`onRollBackward` point)
223
- atomically $ writeTVar chain (slotNum, position - nbBlocks + 1 , blocks, utxo)
224
255
Nothing ->
225
256
pure ()
226
257
227
258
addNewBlockToChain chain transactions =
228
- modifyTVar chain $ \ (slotNum, position, blocks, utxo) ->
259
+ modifyTVar chain $ \ (slotNum, position, blocks, utxo) -> do
229
260
-- NOTE: Assumes 1 slot = 1 second
230
261
let newSlot = slotNum + ChainSlot (truncate blockTime)
231
262
header = genBlockHeaderAt (fromChainSlot newSlot) `generateWith` 42
232
- in case applyTransactions newSlot utxo transactions of
233
- Left err ->
234
- error $
235
- toText $
236
- " On-chain transactions are not supposed to fail: "
237
- <> show err
238
- <> " \n Tx:\n "
239
- <> (show @ String $ txId <$> transactions)
240
- <> " \n UTxO:\n "
241
- <> show (fst <$> pairs utxo)
242
- Right utxo' -> (newSlot, position, blocks :|> (header, transactions, utxo), utxo')
263
+ -- NOTE: Transactions that do not apply to the current state (eg.
264
+ -- UTxO) are silently dropped which emulates the chain behaviour that
265
+ -- only the client is potentially witnessing the failure, and no
266
+ -- invalid transaction will ever be included in the chain.
267
+ (txs', utxo') = collectTransactions ledger newSlot utxo transactions
268
+ in (newSlot, position, blocks :|> (header, txs', utxo'), utxo')
243
269
244
270
-- | Construct fixed 'TimeHandle' that starts from 0 and has the era horizon far in the future.
245
271
-- This is used in our 'Model' tests and we want to make sure the tests finish before
@@ -264,19 +290,20 @@ scriptLedger seedInput =
264
290
where
265
291
initUTxO = fromPairs [(seedInput, (arbitrary >>= genTxOutAdaOnly) `generateWith` 42 )]
266
292
267
- applyTransactions slot utxo = \ case
293
+ -- XXX: We could easily add 'slot' validation here and this would already
294
+ -- emulate the dropping of outdated transactions from the cardano-node
295
+ -- mempool.
296
+ applyTransactions ! slot utxo = \ case
268
297
[] -> Right utxo
269
298
(tx : txs) ->
270
299
case evaluateTx tx utxo of
271
- Left _ ->
272
- -- Transactions that do not apply to the current state (eg. UTxO) are
273
- -- silently dropped which emulates the chain behaviour that only the
274
- -- client is potentially witnessing the failure, and no invalid
275
- -- transaction will ever be included in the chain
276
- applyTransactions slot utxo txs
277
- Right _ ->
278
- let utxo' = adjustUTxO tx utxo
279
- in applyTransactions slot utxo' txs
300
+ Left err ->
301
+ Left (tx, ValidationError {reason = show err})
302
+ Right report
303
+ | any isLeft report ->
304
+ Left (tx, ValidationError {reason = show . lefts $ toList report})
305
+ | otherwise ->
306
+ applyTransactions slot (adjustUTxO tx utxo) txs
280
307
281
308
-- | Find Cardano vkey corresponding to our Hydra vkey using signing keys lookup.
282
309
-- This is a bit cumbersome and a tribute to the fact the `HydraNode` itself has no
0 commit comments