Skip to content

Commit

Permalink
Add a check for restarting a node with different params than the pers…
Browse files Browse the repository at this point in the history
…isted ones
  • Loading branch information
v0d1ch committed Mar 17, 2023
1 parent 2f9df98 commit 87d63ea
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 3 deletions.
37 changes: 34 additions & 3 deletions hydra-node/exe/hydra-node/Main.hs
@@ -1,16 +1,28 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE MultiWayIf #-}

module Main where

import Hydra.Prelude

import Hydra.API.Server (withAPIServer)
import Hydra.Cardano.Api (serialiseToRawBytesHex)
import Hydra.Chain (HeadParameters (..))
import Hydra.Chain.Direct (initialChainState, loadChainContext, mkTinyWallet, withDirectChain)
import Hydra.Chain.Direct.ScriptRegistry (publishHydraScripts)
import Hydra.Chain.Direct.State (ChainStateAt (..))
import Hydra.Chain.Direct.Util (readKeyPair)
import Hydra.HeadLogic (Environment (..), Event (..), HeadState (..), IdleState (..), defaultTTL, getChainState)
import Hydra.HeadLogic (
ClosedState (..),
Environment (..),
Event (..),
HeadState (..),
IdleState (..),
InitialState (..),
OpenState (..),
defaultTTL,
getChainState,
)
import qualified Hydra.Ledger.Cardano as Ledger
import Hydra.Ledger.Cardano.Configuration (
newGlobals,
Expand Down Expand Up @@ -70,9 +82,13 @@ main = do
Nothing -> do
traceWith tracer CreatedState
pure $ Idle IdleState{chainState = initialChainState}
Just a -> do
Just headState -> do
traceWith tracer LoadedState
pure a
case checkRestartParams headState env of
Nothing -> pure headState
Just misconfiguration -> do
traceWith tracer (Misconfiguration misconfiguration)
pure headState
nodeState <- createNodeState hs
ctx <- loadChainContext chainConfig party otherParties hydraScriptsTxId
wallet <- mkTinyWallet (contramap DirectChain tracer) chainConfig
Expand Down Expand Up @@ -110,6 +126,21 @@ main = do

action (Ledger.cardanoLedger globals ledgerEnv)

checkRestartParams :: HeadState Ledger.Tx -> Environment -> Maybe Text
checkRestartParams hs env =
case hs of
Idle _ -> Nothing
Initial InitialState{parameters} -> checkCPAndParties "InitialState" parameters
Open OpenState{parameters} -> checkCPAndParties "OpenState" parameters
Closed ClosedState{parameters} -> checkCPAndParties "ClosedState" parameters
where
checkCPAndParties st params
| Hydra.Chain.contestationPeriod params == cp = Just $ st <> " : " <> "Contestation period does not match"
| Hydra.Chain.parties params == envParties = Just $ st <> " : " <> "Parties mismatch"
| otherwise = Nothing
Environment{contestationPeriod = cp, otherParties, party} = env
envParties = party : otherParties

identifyNode :: RunOptions -> RunOptions
identifyNode opt@RunOptions{verbosity = Verbose "HydraNode", nodeId} = opt{verbosity = Verbose $ "HydraNode-" <> show nodeId}
identifyNode opt = opt
1 change: 1 addition & 0 deletions hydra-node/src/Hydra/Logging/Messages.hs
Expand Up @@ -23,6 +23,7 @@ data HydraLog tx net
| CreatedState
| LoadedState
| NodeOptions {runOptions :: RunOptions}
| Misconfiguration Text
deriving (Generic)

deriving instance (Eq net, Eq (HydraNodeLog tx)) => Eq (HydraLog tx net)
Expand Down

0 comments on commit 87d63ea

Please sign in to comment.