Skip to content

Commit

Permalink
Throw LogicError instead of only logging it
Browse files Browse the repository at this point in the history
  • Loading branch information
abailly-iohk committed Jun 16, 2021
1 parent 44b863c commit ce06ac6
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 3 deletions.
2 changes: 2 additions & 0 deletions hydra-node/src/Hydra/HeadLogic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,6 +155,8 @@ data LogicError tx
| InvalidState (HeadState tx)
| LedgerError ValidationError

instance Tx tx => Exception (LogicError tx)

deriving instance (Eq (HeadState tx), Eq (Event tx)) => Eq (LogicError tx)
deriving instance (Show (HeadState tx), Show (Event tx)) => Show (LogicError tx)

Expand Down
1 change: 1 addition & 0 deletions hydra-node/src/Hydra/Ledger.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ class
, Read tx
, Read (UTxO tx)
, Monoid (UTxO tx)
, Typeable tx
) =>
Tx tx
where
Expand Down
6 changes: 3 additions & 3 deletions hydra-node/src/Hydra/Node.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,10 @@
-- | Top-level module to run a single Hydra node.
module Hydra.Node where

import Cardano.Prelude hiding (STM, async, atomically, cancel, check, poll, threadDelay)
import Cardano.Prelude hiding (STM, async, atomically, cancel, check, poll, threadDelay, throwIO)
import Control.Monad.Class.MonadAsync (MonadAsync, async)
import Control.Monad.Class.MonadSTM (MonadSTM (STM), atomically, newTQueue, newTVar, readTQueue, stateTVar, writeTQueue)
import Control.Monad.Class.MonadThrow (MonadThrow)
import Control.Monad.Class.MonadThrow (MonadThrow, throwIO)
import Control.Monad.Class.MonadTimer (MonadTimer, threadDelay)
import Hydra.HeadLogic (
ClientRequest (..),
Expand Down Expand Up @@ -72,7 +72,7 @@ runHydraNode tracer node@HydraNode{eq} = do
e <- nextEvent eq
traceWith tracer $ ProcessingEvent e
processNextEvent node e >>= \case
Left err -> traceWith tracer (ErrorHandlingEvent e err)
Left err -> traceWith tracer (ErrorHandlingEvent e err) >> throwIO err
Right effs -> forM_ effs (processEffect node tracer) >> traceWith tracer (ProcessedEvent e)

-- | Monadic interface around 'Hydra.Logic.update'.
Expand Down

0 comments on commit ce06ac6

Please sign in to comment.