Skip to content

Commit b49a47a

Browse files
committed
Add HasEventId class to ensure events can be identified
We kept the EventSource/EventSink very abstract to make implementations not realy on the internas of the actual data type used. However, an event source / sink will need at least identify individual events to tell them apart, e.g. to deduplicate them in memory.
1 parent 4150fb2 commit b49a47a

File tree

6 files changed

+117
-114
lines changed

6 files changed

+117
-114
lines changed

hydra-node/src/Hydra/Events.hs

Lines changed: 14 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -6,21 +6,23 @@ module Hydra.Events where
66

77
import Hydra.Prelude
88

9-
-- TODO: Need to add a concept of identification to 'e' as used in these
10-
-- definitions to enable deduplication etc.
9+
-- FIXME(Elaine): we have to figure out a better taxonomy/nomenclature for the events/statechange stuff
10+
-- the eventID here is not the same as the eventID in Queued, that one is more fickle and influenced by non state change events
11+
-- this one is only incremented when we have a new state change event
12+
type EventId = Word64
1113

12-
newtype EventSource e m = EventSource {getEvents' :: m [e]}
14+
class HasEventId a where
15+
getEventId :: a -> EventId
1316

14-
newtype EventSink e m = EventSink {putEvent' :: e -> m ()}
17+
instance HasEventId (EventId, a) where
18+
getEventId = fst
1519

16-
putEventToSinks :: Monad m => [EventSink e m] -> e -> m ()
17-
putEventToSinks sinks e = forM_ sinks (\sink -> putEvent' sink e)
20+
newtype EventSource e m = EventSource {getEvents' :: HasEventId e => m [e]}
1821

19-
putEventsToSinks :: Monad m => [EventSink e m] -> [e] -> m ()
20-
putEventsToSinks sinks es = forM_ es (\e -> putEventToSinks sinks e)
22+
newtype EventSink e m = EventSink {putEvent' :: HasEventId e => e -> m ()}
2123

22-
type EventID = Word64
24+
putEventToSinks :: (Monad m, HasEventId e) => [EventSink e m] -> e -> m ()
25+
putEventToSinks sinks e = forM_ sinks (\sink -> putEvent' sink e)
2326

24-
-- FIXME(Elaine): we have to figure out a better taxonomy/nomenclature for the events/statechange stuff
25-
-- the eventID here is not the same as the eventID in Queued, that one is more fickle and influenced by non state change events
26-
-- this one is only incremented when we have a new state change event
27+
putEventsToSinks :: (Monad m, HasEventId e) => [EventSink e m] -> [e] -> m ()
28+
putEventsToSinks sinks es = forM_ es (\e -> putEventToSinks sinks e)

hydra-node/src/Hydra/HeadLogic/Outcome.hs

Lines changed: 18 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ import Hydra.Prelude
88
import Hydra.API.ServerOutput (ServerOutput)
99
import Hydra.Chain (ChainStateType, HeadParameters, IsChainState, PostChainTx)
1010
import Hydra.Crypto (MultiSignature, Signature)
11+
import Hydra.Events (HasEventId (..))
1112
import Hydra.HeadId (HeadId, HeadSeed)
1213
import Hydra.HeadLogic.Error (LogicError)
1314
import Hydra.HeadLogic.State (HeadState)
@@ -85,23 +86,23 @@ data StateChanged tx
8586
| TickObserved {chainSlot :: ChainSlot, stateChangeID :: Word64}
8687
deriving stock (Generic)
8788

88-
getStateChangeID :: StateChanged tx -> Word64
89-
getStateChangeID = \case
90-
HeadInitialized{stateChangeID} -> stateChangeID
91-
CommittedUTxO{stateChangeID} -> stateChangeID
92-
HeadAborted{stateChangeID} -> stateChangeID
93-
HeadOpened{stateChangeID} -> stateChangeID
94-
TransactionAppliedToLocalUTxO{stateChangeID} -> stateChangeID
95-
SnapshotRequestDecided{stateChangeID} -> stateChangeID
96-
SnapshotRequested{stateChangeID} -> stateChangeID
97-
TransactionReceived{stateChangeID} -> stateChangeID
98-
PartySignedSnapshot{stateChangeID} -> stateChangeID
99-
SnapshotConfirmed{stateChangeID} -> stateChangeID
100-
HeadClosed{stateChangeID} -> stateChangeID
101-
HeadIsReadyToFanout{stateChangeID} -> stateChangeID
102-
HeadFannedOut{stateChangeID} -> stateChangeID
103-
ChainRolledBack{stateChangeID} -> stateChangeID
104-
TickObserved{stateChangeID} -> stateChangeID
89+
instance HasEventId (StateChanged tx) where
90+
getEventId = \case
91+
HeadInitialized{stateChangeID} -> stateChangeID
92+
CommittedUTxO{stateChangeID} -> stateChangeID
93+
HeadAborted{stateChangeID} -> stateChangeID
94+
HeadOpened{stateChangeID} -> stateChangeID
95+
TransactionAppliedToLocalUTxO{stateChangeID} -> stateChangeID
96+
SnapshotRequestDecided{stateChangeID} -> stateChangeID
97+
SnapshotRequested{stateChangeID} -> stateChangeID
98+
TransactionReceived{stateChangeID} -> stateChangeID
99+
PartySignedSnapshot{stateChangeID} -> stateChangeID
100+
SnapshotConfirmed{stateChangeID} -> stateChangeID
101+
HeadClosed{stateChangeID} -> stateChangeID
102+
HeadIsReadyToFanout{stateChangeID} -> stateChangeID
103+
HeadFannedOut{stateChangeID} -> stateChangeID
104+
ChainRolledBack{stateChangeID} -> stateChangeID
105+
TickObserved{stateChangeID} -> stateChangeID
105106

106107
-- FIXME(Elaine): these stateChangeID fields were added in an attempt to make every StateChanged keep track of its ID
107108
-- it's not clear how to handle the state for this. but for now the field is kept so that the type of putEvent' can be kept simple, and shouldn't do harm

hydra-node/test/Hydra/HeadLogicSnapshotSpec.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ import Hydra.HeadLogic (
2424
update,
2525
)
2626
import Hydra.HeadLogic.Outcome (collectEffects)
27-
import Hydra.HeadLogicSpec (getState, getStateAndEventID, inOpenState, inOpenState', runEvents, step)
27+
import Hydra.HeadLogicSpec (getState, getStateAndEventId, inOpenState, inOpenState', runEvents, step)
2828
import Hydra.Ledger (txId)
2929
import Hydra.Ledger.Simple (SimpleTx (..), aValidTx, simpleLedger, utxoRef)
3030
import Hydra.Network.Message (Message (..))
@@ -118,7 +118,7 @@ spec = do
118118

119119
(actualState, actualEventID) <- runEvents (envFor aliceSk) simpleLedger st stEventID $ do
120120
step $ NetworkEvent defaultTTL alice $ ReqTx tx
121-
getStateAndEventID
121+
getStateAndEventId
122122
actualState `shouldBe` st'
123123
actualEventID `shouldBe` st'EventID
124124

@@ -131,7 +131,7 @@ spec = do
131131
step (NetworkEvent defaultTTL carol $ ReqTx $ aValidTx 1)
132132
step (ackFrom carolSk carol)
133133
step (ackFrom aliceSk alice)
134-
getStateAndEventID
134+
getStateAndEventId
135135

136136
let outcome = update bobEnv simpleLedger headStateEventID headState $ ackFrom bobSk bob
137137
collectEffects outcome `shouldSatisfy` sendReqSn
@@ -141,7 +141,7 @@ spec = do
141141
step (NetworkEvent defaultTTL alice $ ReqSn 1 [])
142142
step (ackFrom carolSk carol)
143143
step (ackFrom aliceSk alice)
144-
getStateAndEventID
144+
getStateAndEventId
145145

146146
let outcome = update bobEnv simpleLedger headStateEventID headState $ ackFrom bobSk bob
147147
collectEffects outcome `shouldNotSatisfy` sendReqSn
@@ -160,7 +160,7 @@ spec = do
160160
step (ackFrom carolSk carol)
161161
newTxBeforeSnapshotAcknowledged
162162
step (ackFrom aliceSk alice)
163-
getStateAndEventID
163+
getStateAndEventId
164164

165165
let everybodyAcknowleged = update notLeaderEnv simpleLedger headStateEventID headState $ ackFrom bobSk bob
166166
collectEffects everybodyAcknowleged `shouldNotSatisfy` sendReqSn

0 commit comments

Comments
 (0)