Skip to content

Commit

Permalink
Draft first e2e scenario
Browse files Browse the repository at this point in the history
  • Loading branch information
v0d1ch committed Jul 9, 2024
1 parent 3e8cff2 commit 6f67f00
Show file tree
Hide file tree
Showing 2 changed files with 61 additions and 1 deletion.
55 changes: 55 additions & 0 deletions hydra-cluster/src/Hydra/Cluster/Scenarios.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,8 @@ import Network.HTTP.Req (
import System.Directory (removeDirectoryRecursive)
import System.FilePath ((</>))
import Test.QuickCheck (choose, generate)
import Hydra.Options (ChainConfig(..))
import Network.HTTP.Simple (setRequestBodyJSON, httpJSON, getResponseBody)

data EndToEndLog
= ClusterOptions {options :: Options}
Expand Down Expand Up @@ -398,6 +400,59 @@ singlePartyCommitsFromExternalTxBlueprint tracer workDir node hydraScriptsTxId =
where
RunningNode{networkId, nodeSocket, blockTime} = node

-- | Open a a single participant head with some UTxO and then commit some UTxO to a running Head.
canCommit :: Tracer IO EndToEndLog -> FilePath -> RunningNode -> TxId -> IO ()
canCommit tracer workDir node hydraScriptsTxId =
(`finally` returnFundsToFaucet tracer node Alice) $ do
refuelIfNeeded tracer node Alice 30_000_000
-- Start hydra-node on chain tip
tip <- queryTip networkId nodeSocket
let contestationPeriod = UnsafeContestationPeriod 100
aliceChainConfig <-
chainConfigFor Alice workDir nodeSocket hydraScriptsTxId [] contestationPeriod
<&> \case
Direct cfg -> Direct cfg{networkId, startChainFrom = Just tip}
_ -> error "Should not be in offline mode"
withHydraNode hydraTracer aliceChainConfig workDir 1 aliceSk [] [1] $ \n1@HydraClient{hydraNodeId} -> do
-- Setup an open head
send n1 $ input "Init" []
headId <- waitMatch 10 n1 $ headIsInitializingWith (Set.fromList [alice])
(walletVk, walletSk) <- generate genKeyPair
commitUTxO <- seedFromFaucet node walletVk 10_000_000 (contramap FromFaucet tracer)
requestCommitTx n1 commitUTxO <&> signTx walletSk >>= submitTx node
waitFor hydraTracer 10 [n1] $
output "HeadIsOpen" ["utxo" .= commitUTxO, "headId" .= headId]

-- Incrementally commit utxo to the head
incrementalCommitUTxO <- seedFromFaucet node walletVk 5_000_000 (contramap FromFaucet tracer)

incrementTx <-
L.parseUrlThrow ("POST http://127.0.0.1:" <> show (4000 + hydraNodeId) <> "/commit")
<&> setRequestBodyJSON incrementalCommitUTxO
>>= httpJSON
<&> getResponseBody
-- Requesting the commit above would already trigger these server outputs.
-- Hence, when we return from the API call, these outputs must already
-- have been received on the websocket.
-- TODO: could concurrently wait for this and the server outputs instead of these short timeouts
waitFor hydraTracer 0.1 [n1] $
output "CommitRequested" ["headId" .= headId, "utxoToCommit" .= incrementalCommitUTxO]
waitFor hydraTracer 0.1 [n1] $
output "CommitApproved" ["headId" .= headId, "utxoToCommit" .= incrementalCommitUTxO]

-- Submitting the transaction will finalize the commit (and enable more commits)
submitTx node $ signTx walletSk incrementTx
waitFor hydraTracer 10 [n1] $
output "CommitFinalized" ["headId" .= headId]

send n1 $ input "GetUTxO" []
waitFor hydraTracer 10 [n1] $
output "GetUTxOResponse" ["headId" .= headId, "utxo" .= (commitUTxO <> incrementalCommitUTxO)]
where
hydraTracer = contramap FromHydraNode tracer

RunningNode{networkId, nodeSocket} = node

-- | Initialize open and close a head on a real network and ensure contestation
-- period longer than the time horizon is possible. For this it is enough that
-- we can close a head and not wait for the deadline.
Expand Down
7 changes: 6 additions & 1 deletion hydra-cluster/test/Test/EndToEndSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ import Hydra.Cluster.Scenarios (
singlePartyCommitsFromExternalTxBlueprint,
singlePartyHeadFullLifeCycle,
testPreventResumeReconfiguredPeer,
threeNodesNoErrorsOnOpen,
threeNodesNoErrorsOnOpen, canCommit,
)
import Hydra.Cluster.Util (chainConfigFor, keysFor, modifyConfig)
import Hydra.ContestationPeriod (ContestationPeriod (UnsafeContestationPeriod))
Expand Down Expand Up @@ -192,6 +192,11 @@ spec = around (showLogsOnFailure "EndToEndSpec") $ do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \node ->
publishHydraScriptsAs node Faucet
>>= singlePartyCommitsFromExternalTxBlueprint tracer tmpDir node
it "can incrementally commit utxo" $ \tracer -> do
withClusterTempDir $ \tmpDir -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \node ->
publishHydraScriptsAs node Faucet
>>= canCommit tracer tmpDir node

describe "three hydra nodes scenario" $ do
it "does not error when all nodes open the head concurrently" $ \tracer ->
Expand Down

0 comments on commit 6f67f00

Please sign in to comment.