Skip to content

Commit

Permalink
Problems with rollback management
Browse files Browse the repository at this point in the history
We do not handle rollbacks correctly:
* a client would not now what to do with a rollback event
* we do not handle these events correctly

[#185](#185) is about
dealing appropriately with the rollback.

With [#185](#185)
we will be able to really solve the issues in an appropriate way for
both, the client using a hydra-node and the internals of our system.
In the mean time, we remove the rollback logic from Hydra head so that:
* we do not send rollback events to the client
* we _bet_ that the seen transactions will be seen again in the new fork
  of the chain

TODO:
* add the chainState to the rollback event so that we remove all the rollback
  logic from HeadLogic
  • Loading branch information
pgrange authored and v0d1ch committed Apr 26, 2023
1 parent 31c80e9 commit bce9249
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 21 deletions.
19 changes: 18 additions & 1 deletion hydra-node/src/Hydra/HeadLogic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -970,7 +970,16 @@ onCurrentChainRollback ::
ChainSlot ->
Outcome tx
onCurrentChainRollback currentState slot =
NewState (rollback slot currentState) [ClientEffect RolledBack]
let atTheTimeState = rollback slot currentState
in case atTheTimeState of
Idle IdleState{chainState} ->
NewState (updateChainState chainState currentState) []
Initial InitialState{chainState} ->
NewState (updateChainState chainState currentState) []
Open OpenState{chainState} ->
NewState (updateChainState chainState currentState) []
Closed ClosedState{chainState} ->
NewState (updateChainState chainState currentState) []
where
-- TODO use slot instead of local rollbackSlot argument
rollback rollbackSlot hs
Expand All @@ -984,6 +993,14 @@ onCurrentChainRollback currentState slot =
rollback rollbackSlot previousRecoverableState
Closed ClosedState{previousRecoverableState} ->
rollback rollbackSlot previousRecoverableState
updateChainState chainState = \case
Idle s@IdleState{} -> Idle s{chainState}
Initial s@InitialState{} ->
Initial s{chainState}
Open s@OpenState{} ->
Open s{chainState}
Closed s@ClosedState{} ->
Closed s{chainState}

-- | The "pure core" of the Hydra node, which handles the 'Event' against a
-- current 'HeadState'. Resulting new 'HeadState's are retained and 'Effect'
Expand Down
16 changes: 9 additions & 7 deletions hydra-node/test/Hydra/BehaviorSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -455,7 +455,7 @@ spec = parallel $ do

roundtripAndGoldenSpecs (Proxy @(HydraNodeLog SimpleTx))

describe "rolling back & forward" $ do
describe "rolling back & forward does not make the node crash" $ do
it "does work for rollbacks past init" $
shouldRunInSim $ do
withSimulatedChainAndNetwork $ \chain ->
Expand All @@ -464,8 +464,9 @@ spec = parallel $ do
waitUntil [n1] $ HeadIsInitializing testHeadId (fromList [alice])
-- We expect the Init to be rolled back and forward again
rollbackAndForward chain 1
waitUntil [n1] RolledBack
waitUntil [n1] $ HeadIsInitializing testHeadId (fromList [alice])
-- We expect the node to still work and let us commit
send n1 (Commit (utxoRef 1))
waitUntil [n1] $ Committed testHeadId alice (utxoRef 1)

it "does work for rollbacks past open" $
shouldRunInSim $ do
Expand All @@ -479,9 +480,9 @@ spec = parallel $ do
-- We expect one Commit AND the CollectCom to be rolled back and
-- forward again
rollbackAndForward chain 2
waitUntil [n1] RolledBack
waitUntil [n1] $ Committed testHeadId alice (utxoRef 1)
waitUntil [n1] $ HeadIsOpen{headId = testHeadId, utxo = utxoRefs [1]}
-- We expect the node to still work and let us post L2 transactions
send n1 (NewTx (aValidTx 42))
waitUntil [n1] $ TxValid testHeadId (aValidTx 42)

-- | Wait for some output at some node(s) to be produced /eventually/. See
-- 'waitUntilMatch' for how long it waits.
Expand Down Expand Up @@ -543,7 +544,8 @@ data TestHydraNode tx m = TestHydraNode
data ConnectToChain tx m = ConnectToChain
{ chainComponent :: HydraNode tx m -> m (HydraNode tx m)
, tickThread :: Async m ()
, rollbackAndForward :: Natural -> m ()
, -- TODO remove the following if we really don't use it anymore
rollbackAndForward :: Natural -> m ()
}

-- | With-pattern wrapper around 'simulatedChainAndNetwork' which does 'cancel'
Expand Down
8 changes: 0 additions & 8 deletions hydra-node/test/Hydra/HeadLogicSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,6 @@ import Hydra.Party (Party (..))
import Hydra.Snapshot (ConfirmedSnapshot (..), Snapshot (..), getSnapshot)
import Test.Aeson.GenericSpecs (roundtripAndGoldenSpecs)
import Test.Hydra.Fixture (alice, aliceSk, bob, bobSk, carol, carolSk, cperiod)
import Test.QuickCheck (forAll)
import Test.QuickCheck.Monadic (monadicIO, run)

spec :: Spec
spec = do
Expand Down Expand Up @@ -286,12 +284,6 @@ spec = do
s2 = update bobEnv ledger s1 stepTimePastDeadline
s2 `hasEffect` ClientEffect (ReadyToFanout testHeadId)

it "notify user on rollback" $
forAll arbitrary $ \s -> monadicIO $ do
let rollback = OnChainEvent (Rollback $ ChainSlot 2)
let s' = update bobEnv ledger s rollback
void $ run $ s' `hasEffect` ClientEffect RolledBack

it "contests when detecting close with old snapshot" $ do
let snapshot = Snapshot 2 mempty []
latestConfirmedSnapshot = ConfirmedSnapshot snapshot (aggregate [])
Expand Down
6 changes: 1 addition & 5 deletions hydra-node/test/Hydra/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -192,11 +192,7 @@ instance StateModel WorldState where
, (1, genAbort)
]
Open{} -> do
-- FIXME: Generation of arbitrary NewTx disabled as we don't control
-- rollbacks in the MockChain and the hydra-node purges L2 state when
-- rolling back "past open".
void genNewTx
pure $ Error "NewTx disabled because of rollbacks past open"
genNewTx
_ -> fmap Some genSeed
where
genCommit pending = do
Expand Down

0 comments on commit bce9249

Please sign in to comment.