Skip to content

Commit

Permalink
WIP: try to re-use withHydraNode in misconfig e2e test
Browse files Browse the repository at this point in the history
  • Loading branch information
ch1bo committed Jul 31, 2023
1 parent a6fbe49 commit 7834ce7
Show file tree
Hide file tree
Showing 2 changed files with 94 additions and 82 deletions.
20 changes: 9 additions & 11 deletions hydra-cluster/src/HydraNode.hs
Expand Up @@ -49,6 +49,8 @@ data HydraClient = HydraClient
{ hydraNodeId :: Int
, connection :: Connection
, tracer :: Tracer IO EndToEndLog
, hydraNodeStdout :: Handle
, hydraNodeStderr :: Handle
}

-- | Create an input as expected by 'send'.
Expand Down Expand Up @@ -317,15 +319,16 @@ withHydraNode tracer chainConfig workDir hydraNodeId hydraSKey hydraVKeys allNod
}
)
{ std_out = UseHandle out
, std_err = CreatePipe
}
withCreateProcess p $
\_stdin _stdout _stderr processHandle -> do
\_stdin Nothing (Just err) processHandle -> do
result <-
race
(checkProcessHasNotDied ("hydra-node (" <> show hydraNodeId <> ")") processHandle)
(withConnectionToNode tracer hydraNodeId action)
(withConnectionToNode tracer hydraNodeId (undefined, err) action)
case result of
Left err -> absurd err
Left e -> absurd e
Right a -> pure a
where
logFilePath = workDir </> "logs" </> "hydra-node-" <> show hydraNodeId <.> "log"
Expand All @@ -339,8 +342,8 @@ withHydraNode tracer chainConfig workDir hydraNodeId hydraSKey hydraVKeys allNod
, i /= hydraNodeId
]

withConnectionToNode :: Tracer IO EndToEndLog -> Int -> (HydraClient -> IO a) -> IO a
withConnectionToNode tracer hydraNodeId action = do
withConnectionToNode :: Tracer IO EndToEndLog -> Int -> (Handle, Handle) -> (HydraClient -> IO a) -> IO a
withConnectionToNode tracer hydraNodeId (hydraNodeStdout, hydraNodeStderr) action = do
connectedOnce <- newIORef False
tryConnect connectedOnce
where
Expand All @@ -353,15 +356,10 @@ withConnectionToNode tracer hydraNodeId action = do
doConnect connectedOnce = runClient "127.0.0.1" (4000 + hydraNodeId) "/" $ \connection -> do
atomicWriteIORef connectedOnce True
traceWith tracer (NodeStarted hydraNodeId)
res <- action $ HydraClient{hydraNodeId, connection, tracer}
res <- action $ HydraClient{hydraNodeId, connection, tracer, hydraNodeStdout, hydraNodeStderr}
sendClose connection ("Bye" :: Text)
pure res

-- | Runs an action with a new connection to given Hydra node.
withNewClient :: HydraClient -> (HydraClient -> IO a) -> IO a
withNewClient HydraClient{hydraNodeId, tracer} =
withConnectionToNode tracer hydraNodeId

hydraNodeProcess :: RunOptions -> CreateProcess
hydraNodeProcess = proc "hydra-node" . toArgs

Expand Down
156 changes: 85 additions & 71 deletions hydra-cluster/test/Test/EndToEndSpec.hs
Expand Up @@ -18,7 +18,6 @@ import Data.Aeson (Result (..), Value (Null, Object, String), fromJSON, object,
import qualified Data.Aeson as Aeson
import Data.Aeson.Lens (key, values, _JSON)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Text (pack)
Expand All @@ -31,7 +30,6 @@ import Hydra.Cardano.Api (
NetworkMagic (NetworkMagic),
PaymentKey,
SlotNo (..),
Tx,
TxId,
TxIn (..),
VerificationKey,
Expand All @@ -42,7 +40,6 @@ import Hydra.Cardano.Api (
writeFileTextEnvelope,
pattern TxValidityLowerBound,
)
import Hydra.Chain (HeadParameters (contestationPeriod, parties))
import Hydra.Chain.Direct.State ()
import Hydra.Cluster.Faucet (
Marked (Fuel, Normal),
Expand All @@ -65,6 +62,7 @@ import Hydra.Cluster.Fixture (
import Hydra.Cluster.Scenarios (
canCloseWithLongContestationPeriod,
headIsInitializingWith,
refuelIfNeeded,
restartedNodeCanAbort,
restartedNodeCanObserveCommitTx,
singlePartyCannotCommitExternallyWalletUtxo,
Expand All @@ -75,15 +73,14 @@ import Hydra.Cluster.Scenarios (
import Hydra.Cluster.Util (chainConfigFor, keysFor)
import Hydra.ContestationPeriod (ContestationPeriod (UnsafeContestationPeriod))
import Hydra.Crypto (HydraKey, generateSigningKey)
import Hydra.HeadLogic (HeadState (Open), OpenState (parameters))
import Hydra.Ledger (txId)
import Hydra.Ledger.Cardano (genKeyPair, mkRangedTx, mkSimpleTx)
import Hydra.Logging (Tracer, showLogsOnFailure)
import Hydra.Options
import Hydra.Party (deriveParty)
import HydraNode (
EndToEndLog (..),
HydraClient,
HydraClient (..),
externalCommit,
getMetrics,
input,
Expand All @@ -96,13 +93,13 @@ import HydraNode (
withHydraCluster,
withHydraNode,
)
import System.Directory (createDirectoryIfMissing, removeDirectoryRecursive)
import System.Directory (removeDirectoryRecursive)
import System.FilePath ((</>))
import System.IO (hGetLine)
import System.IO.Error (isEOFError)
import System.Process (CreateProcess (..), StdStream (..), proc, withCreateProcess)
import System.Timeout (timeout)
import Test.QuickCheck (generate, suchThat)
import Test.QuickCheck (generate)
import qualified Prelude

allNodeIds :: [Int]
Expand Down Expand Up @@ -425,71 +422,88 @@ spec = around showLogsOnFailure $

it "detects misconfiguration" $ \tracer -> do
withClusterTempDir "detect-misconfiguration" $ \dir -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) dir $ \node@RunningNode{nodeSocket} -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) dir $ \node@RunningNode{nodeSocket, networkId} -> do
hydraScriptsTxId <- publishHydraScriptsAs node Faucet
let persistenceDir = dir </> "persistence"
let cardanoSK = dir </> "cardano.sk"
let hydraSK = dir </> "hydra.sk"

(_, cardanoSKey) <- generateCardanoKey
hydraSKey :: SigningKey HydraKey <- generate arbitrary

void $ writeFileTextEnvelope hydraSK Nothing hydraSKey
void $ writeFileTextEnvelope cardanoSK Nothing cardanoSKey

-- generate node state to save to a file
openState :: OpenState Tx <- generate arbitrary
let headParameters = parameters openState
stateContestationPeriod = Hydra.Chain.contestationPeriod headParameters

-- generate one value for CP different from what we have in the state
differentContestationPeriod <- generate $ arbitrary `suchThat` (/= stateContestationPeriod)

-- alter the state to trigger the errors
let alteredNodeState =
Open
( openState
{ parameters =
headParameters{contestationPeriod = differentContestationPeriod, parties = []}
}
)

-- save altered node state
void $ do
createDirectoryIfMissing True persistenceDir
BSL.writeFile (persistenceDir </> "state") (Aeson.encode alteredNodeState)

let nodeArgs =
toArgs
defaultRunOptions
{ chainConfig =
defaultChainConfig
{ cardanoSigningKey = cardanoSK
, nodeSocket
, contestationPeriod = Hydra.Chain.contestationPeriod headParameters
}
, hydraSigningKey = hydraSK
, hydraScriptsTxId
, persistenceDir
, ledgerConfig =
defaultLedgerConfig
{ cardanoLedgerProtocolParametersFile = "config/protocol-parameters.json"
}
}

-- expecting misconfiguration
withCreateProcess (proc "hydra-node" nodeArgs){std_out = CreatePipe, std_err = CreatePipe} $
\_ (Just nodeStdout) (Just nodeStdErr) _ -> do
-- we should be able to observe the log
waitForLog 10 nodeStdout "Detect Misconfiguration log" $ \outline ->
outline ^? key "message" . key "tag" == Just (Aeson.String "Misconfiguration")

-- node should exit with appropriate exception
waitForLog 10 nodeStdErr "Detect ParamMismatchError" $ \errline ->
let allLogLines = lines errline
expectedLog =
"hydra-node: ParamMismatchError \"Loaded state does not match given command line options. Please check the state in: " <> pack persistenceDir <> " against provided command line options.\""
in expectedLog `elem` allLogLines
refuelIfNeeded tracer node Alice 100_000_000
let contestationPeriod = UnsafeContestationPeriod 2
aliceChainConfig <-
chainConfigFor Alice dir nodeSocket [] contestationPeriod
-- we delibelately do not start from a chain point here to highlight the
-- need for persistence
<&> \config -> config{networkId, startChainFrom = Nothing}

headId1 <- withHydraNode tracer aliceChainConfig dir 1 aliceSk [] [1] hydraScriptsTxId $ \n1 -> do
send n1 $ input "Init" []
-- XXX: might need to tweak the wait time
waitMatch 10 n1 $ headIsInitializingWith (Set.fromList [alice])

-- let persistenceDir = dir </> "persistence"
-- let cardanoSK = dir </> "cardano.sk"
-- let hydraSK = dir </> "hydra.sk"

-- (_, cardanoSKey) <- generateCardanoKey
-- hydraSKey :: SigningKey HydraKey <- generate arbitrary

-- void $ writeFileTextEnvelope hydraSK Nothing hydraSKey
-- void $ writeFileTextEnvelope cardanoSK Nothing cardanoSKey

-- -- generate node state to save to a file
-- openState :: OpenState Tx <- generate arbitrary
-- let headParameters = parameters openState
-- stateContestationPeriod = Hydra.Chain.contestationPeriod headParameters

-- -- generate one value for CP different from what we have in the state
-- differentContestationPeriod <- generate $ arbitrary `suchThat` (/= stateContestationPeriod)

-- -- alter the state to trigger the errors
-- let alteredNodeState =
-- Open
-- ( openState
-- { parameters =
-- headParameters{contestationPeriod = differentContestationPeriod, parties = []}
-- }
-- )

-- -- save altered node state
-- void $ do
-- createDirectoryIfMissing True persistenceDir
-- BSL.writeFile (persistenceDir </> "state") (Aeson.encode alteredNodeState)

-- let nodeArgs =
-- toArgs
-- defaultRunOptions
-- { chainConfig =
-- defaultChainConfig
-- { cardanoSigningKey = cardanoSK
-- , nodeSocket
-- , contestationPeriod = Hydra.Chain.contestationPeriod headParameters
-- }
-- , hydraSigningKey = hydraSK
-- , hydraScriptsTxId
-- , persistenceDir
-- , ledgerConfig =
-- defaultLedgerConfig
-- { cardanoLedgerProtocolParametersFile = "config/protocol-parameters.json"
-- }
-- }

let mismatchedConfig = aliceChainConfig{contestationPeriod = UnsafeContestationPeriod 10}
withHydraNode tracer mismatchedConfig dir 1 aliceSk [] [1] hydraScriptsTxId $ \n1 -> do
let HydraClient{hydraNodeStderr} = n1
-- withCreateProcess (proc "hydra-node" nodeArgs){std_out = CreatePipe, std_err = CreatePipe} $
-- \_ (Just nodeStdout) (Just nodeStdErr) _ -> do
-- we should be able to observe the log
-- TODO: check logs instead
-- waitForLog 10 hydraNodeStdout "Detect Misconfiguration log" $ \outline ->
-- outline ^? key "message" . key "tag" == Just (Aeson.String "Misconfiguration")

-- node should exit with appropriate exception
waitForLog 10 hydraNodeStderr "Detect ParamMismatchError" $ \errline ->
let allLogLines = lines errline
-- FIXME: do not compare full strings!
expectedLog =
"hydra-node: ParamMismatchError \"Loaded state does not match given command line options. Please check the state in: " <> pack dir <> " against provided command line options.\""
in expectedLog `elem` allLogLines

waitForLog :: NominalDiffTime -> Handle -> Text -> (Text -> Bool) -> IO ()
waitForLog delay nodeOutput failureMessage predicate = do
Expand Down

0 comments on commit 7834ce7

Please sign in to comment.