Skip to content

Commit

Permalink
Fix and rename integration tests
Browse files Browse the repository at this point in the history
  • Loading branch information
ch1bo committed Jan 31, 2025
1 parent a5c6dca commit e3b9cda
Show file tree
Hide file tree
Showing 3 changed files with 90 additions and 86 deletions.
4 changes: 2 additions & 2 deletions hydra-explorer/hydra-explorer.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -103,9 +103,9 @@ test-suite tests
, yaml

other-modules:
Hydra.Explorer.ApiSpec
Hydra.Explorer.ExplorerStateSpec
Hydra.Explorer.HydraExplorerSpec
Hydra.ExplorerSpec
Hydra.Explorer.IntegrationSpec
Spec

build-tool-depends:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

-- | Tests that the hydra-explorer client API endpoints correspond to the
-- advertised openapi specification.
module Hydra.ExplorerSpec where
module Hydra.Explorer.ApiSpec where

import Hydra.Prelude hiding (get)
import Test.Hydra.Prelude
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

-- | Integration tests for the 'hydra-explorer' executable. These will run
-- also 'hydra-node' on a devnet and assert correct observation.
module Hydra.Explorer.HydraExplorerSpec where
module Hydra.Explorer.IntegrationSpec where

import Hydra.Prelude hiding (get)
import Test.Hydra.Prelude
Expand Down Expand Up @@ -34,11 +34,11 @@ spec = do
-- hydra-explorer.
it "aggregates observations" $
failAfter 60 $
showLogsOnFailure "HydraExplorerSpec" $ \tracer -> do
showLogsOnFailure "IntegrationSpec" $ \tracer -> do
withTempDir "hydra-explorer-history" $ \tmpDir -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \node -> do
hydraScriptsTxId <- publishHydraScriptsAs node Faucet
withHydraExplorer $ \explorer -> do
withHydraExplorer $ \explorer -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \node -> do
hydraScriptsTxId <- publishHydraScriptsAs node Faucet
withChainObserver node explorer $ do
-- Open and close a head
singlePartyHeadFullLifeCycle (contramap FromScenario tracer) tmpDir node hydraScriptsTxId
Expand All @@ -52,97 +52,101 @@ spec = do
-- to be covered in the main hydra repo)
it "can observe hydra transactions created by multiple hydra-nodes" $
failAfter 60 $
showLogsOnFailure "HydraExplorerSpec" $ \tracer -> do
showLogsOnFailure "IntegrationSpec" $ \tracer -> do
withTempDir "hydra-explorer-history" $ \tmpDir -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \cardanoNode@RunningNode{nodeSocket} -> do
let hydraTracer = contramap FromHydraNode tracer
hydraScriptsTxId <- publishHydraScriptsAs cardanoNode Faucet
withHydraExplorer $ \explorer -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \cardanoNode@RunningNode{nodeSocket} -> do
withChainObserver cardanoNode explorer $ do
let hydraTracer = contramap FromHydraNode tracer
hydraScriptsTxId <- publishHydraScriptsAs cardanoNode Faucet

let initHead hydraNode = do
send hydraNode $ input "Init" []
waitMatch 5 hydraNode $ \v -> do
guard $ v ^? key "tag" == Just "HeadIsInitializing"
v ^? key "headId" . _String

let depositDeadline = UnsafeDepositDeadline 200
(aliceCardanoVk, _aliceCardanoSk) <- keysFor Alice
aliceChainConfig <- chainConfigFor Alice tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode aliceCardanoVk 25_000_000 (contramap FromFaucet tracer)
aliceHeadId <- withHydraNode hydraTracer aliceChainConfig tmpDir 1 aliceSk [] [1] initHead

(bobCardanoVk, _bobCardanoSk) <- keysFor Bob
bobChainConfig <- chainConfigFor Bob tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode bobCardanoVk 25_000_000 (contramap FromFaucet tracer)
bobHeadId <- withHydraNode hydraTracer bobChainConfig tmpDir 2 bobSk [] [2] initHead

let initHead hydraNode = do
allHeads <- getHeads explorer
length (allHeads ^. _Array) `shouldBe` 2
allHeads ^. nth 0 . key "headId" . _String `shouldBe` aliceHeadId
allHeads ^. nth 0 . key "status" . _String `shouldBe` "Initializing"
allHeads ^. nth 1 . key "headId" . _String `shouldBe` bobHeadId
allHeads ^. nth 1 . key "status" . _String `shouldBe` "Initializing"

it "can query for all hydra heads observed" $
failAfter 60 $
showLogsOnFailure "IntegrationSpec" $ \tracer -> do
withTempDir "hydra-explorer-get-heads" $ \tmpDir -> do
withHydraExplorer $ \explorer -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \cardanoNode@RunningNode{nodeSocket} -> do
withChainObserver cardanoNode explorer $ do
let hydraTracer = contramap FromHydraNode tracer
hydraScriptsTxId <- publishHydraScriptsAs cardanoNode Faucet
let depositDeadline = UnsafeDepositDeadline 200
(aliceCardanoVk, _aliceCardanoSk) <- keysFor Alice
aliceChainConfig <- chainConfigFor Alice tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode aliceCardanoVk 25_000_000 (contramap FromFaucet tracer)
aliceHeadId <- withHydraNode hydraTracer aliceChainConfig tmpDir 1 aliceSk [] [1] $ \hydraNode -> do
send hydraNode $ input "Init" []

waitMatch 5 hydraNode $ \v -> do
guard $ v ^? key "tag" == Just "HeadIsInitializing"
v ^? key "headId" . _String

let depositDeadline = UnsafeDepositDeadline 200
(aliceCardanoVk, _aliceCardanoSk) <- keysFor Alice
aliceChainConfig <- chainConfigFor Alice tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode aliceCardanoVk 25_000_000 (contramap FromFaucet tracer)
aliceHeadId <- withHydraNode hydraTracer aliceChainConfig tmpDir 1 aliceSk [] [1] initHead

(bobCardanoVk, _bobCardanoSk) <- keysFor Bob
bobChainConfig <- chainConfigFor Bob tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode bobCardanoVk 25_000_000 (contramap FromFaucet tracer)
bobHeadId <- withHydraNode hydraTracer bobChainConfig tmpDir 2 bobSk [] [2] initHead

withHydraExplorer $ \explorer -> do
allHeads <- getHeads explorer
length (allHeads ^. _Array) `shouldBe` 2
allHeads ^. nth 0 . key "headId" . _String `shouldBe` aliceHeadId
allHeads ^. nth 0 . key "status" . _String `shouldBe` "Initializing"
allHeads ^. nth 1 . key "headId" . _String `shouldBe` bobHeadId
allHeads ^. nth 1 . key "status" . _String `shouldBe` "Initializing"
(bobCardanoVk, _bobCardanoSk) <- keysFor Bob
bobChainConfig <- chainConfigFor Bob tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode bobCardanoVk 25_000_000 (contramap FromFaucet tracer)
bobHeadId <- withHydraNode hydraTracer bobChainConfig tmpDir 2 bobSk [] [2] $ \hydraNode -> do
send hydraNode $ input "Init" []

it "can query for all hydra heads observed" $
failAfter 60 $
showLogsOnFailure "HydraExplorerSpec" $ \tracer -> do
withTempDir "hydra-explorer-get-heads" $ \tmpDir -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \cardanoNode@RunningNode{nodeSocket} -> do
let hydraTracer = contramap FromHydraNode tracer
hydraScriptsTxId <- publishHydraScriptsAs cardanoNode Faucet
withHydraExplorer $ \explorer -> do
let depositDeadline = UnsafeDepositDeadline 200
(aliceCardanoVk, _aliceCardanoSk) <- keysFor Alice
aliceChainConfig <- chainConfigFor Alice tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode aliceCardanoVk 25_000_000 (contramap FromFaucet tracer)
aliceHeadId <- withHydraNode hydraTracer aliceChainConfig tmpDir 1 aliceSk [] [1] $ \hydraNode -> do
send hydraNode $ input "Init" []

waitMatch 5 hydraNode $ \v -> do
guard $ v ^? key "tag" == Just "HeadIsInitializing"
v ^? key "headId" . _String

(bobCardanoVk, _bobCardanoSk) <- keysFor Bob
bobChainConfig <- chainConfigFor Bob tmpDir nodeSocket hydraScriptsTxId [] cperiod depositDeadline
seedFromFaucet_ cardanoNode bobCardanoVk 25_000_000 (contramap FromFaucet tracer)
bobHeadId <- withHydraNode hydraTracer bobChainConfig tmpDir 2 bobSk [] [2] $ \hydraNode -> do
send hydraNode $ input "Init" []

bobHeadId <- waitMatch 5 hydraNode $ \v -> do
guard $ v ^? key "tag" == Just "HeadIsInitializing"
v ^? key "headId" . _String

send hydraNode $ input "Abort" []

waitMatch 5 hydraNode $ \v -> do
guard $ v ^? key "tag" == Just "HeadIsAborted"
guard $ v ^? key "headId" . _String == Just bobHeadId

pure bobHeadId

allHeads <- getHeads explorer
length (allHeads ^. _Array) `shouldBe` 2
allHeads ^. nth 0 . key "headId" . _String `shouldBe` aliceHeadId
allHeads ^. nth 0 . key "status" . _String `shouldBe` "Initializing"
allHeads ^. nth 1 . key "headId" . _String `shouldBe` bobHeadId
allHeads ^. nth 1 . key "status" . _String `shouldBe` "Aborted"
bobHeadId <- waitMatch 5 hydraNode $ \v -> do
guard $ v ^? key "tag" == Just "HeadIsInitializing"
v ^? key "headId" . _String

send hydraNode $ input "Abort" []

waitMatch 5 hydraNode $ \v -> do
guard $ v ^? key "tag" == Just "HeadIsAborted"
guard $ v ^? key "headId" . _String == Just bobHeadId

pure bobHeadId

allHeads <- getHeads explorer
length (allHeads ^. _Array) `shouldBe` 2
allHeads ^. nth 0 . key "headId" . _String `shouldBe` aliceHeadId
allHeads ^. nth 0 . key "status" . _String `shouldBe` "Initializing"
allHeads ^. nth 1 . key "headId" . _String `shouldBe` bobHeadId
allHeads ^. nth 1 . key "status" . _String `shouldBe` "Aborted"

it "can query for latest point in time observed on chain" $
failAfter 60 $
showLogsOnFailure "HydraExplorerSpec" $ \tracer -> do
showLogsOnFailure "IntegrationSpec" $ \tracer -> do
withTempDir "hydra-explorer-get-tick" $ \tmpDir -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \RunningNode{nodeSocket, networkId} -> do
withHydraExplorer $ \explorer -> do
tip <- toJSON <$> queryTip networkId nodeSocket
tick <- getTick explorer
withHydraExplorer $ \explorer -> do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \node@RunningNode{nodeSocket, networkId} -> do
withChainObserver node explorer $ do
threadDelay 1
tip <- toJSON <$> queryTip networkId nodeSocket
tick <- getTick explorer

let tipSlot = tip ^? key "slot" . _Number
tickSlot = tick ^? key "point" . key "slot" . _Number
tipSlot `shouldBe` tickSlot
let tipSlot = tip ^? key "slot" . _Number
tickSlot = tick ^? key "point" . key "slot" . _Number
tickSlot `shouldBe` tipSlot

let tipBlockHash = tip ^? key "blockHash" . _String
tickBlockHash = tick ^? key "point" . key "blockHash" . _String
tipBlockHash `shouldBe` tickBlockHash
let tipBlockHash = tip ^? key "blockHash" . _String
tickBlockHash = tick ^? key "point" . key "blockHash" . _String
tickBlockHash `shouldBe` tipBlockHash

-- * Running hydra-explorer

Expand All @@ -164,7 +168,7 @@ withHydraExplorer action =
<> ["--observer-port", show observerPort]
withProcessExpect process $ \_p -> do
-- XXX: wait for the http server to be listening on port
threadDelay 3
threadDelay 1
action
HydraExplorerClient
{ clientPort
Expand Down

0 comments on commit e3b9cda

Please sign in to comment.