Skip to content

Commit

Permalink
break down e2e
Browse files Browse the repository at this point in the history
  • Loading branch information
ffakenz committed Nov 13, 2024
1 parent 801ac7f commit 5c701e2
Showing 1 changed file with 155 additions and 102 deletions.
257 changes: 155 additions & 102 deletions hydra-cluster/test/Test/Hydra/Cluster/HydraClientSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import CardanoNode (
withCardanoNodeDevnet,
)
import Control.Lens ((^?))
import Data.Aeson (Value (..), object, (.=))
import Data.Aeson (Value (..), (.=))
import Data.Aeson.Lens (key)
import Data.Set qualified as Set
import Data.Text qualified as Text
Expand Down Expand Up @@ -43,7 +43,7 @@ import Hydra.Ledger.Cardano (mkSimpleTx)
import Hydra.Logging (Tracer, showLogsOnFailure)
import Hydra.Tx (IsTx (..))
import Hydra.Tx.ContestationPeriod (ContestationPeriod (UnsafeContestationPeriod))
import HydraNode (HydraClient (..), input, output, requestCommitTx, send, waitFor, waitForAllMatch, waitForNodesConnected, waitMatch, withConnectionToNodeHost, withHydraCluster)
import HydraNode (HydraClient (..), HydraNodeLog, input, output, requestCommitTx, send, waitFor, waitForAllMatch, waitForNodesConnected, waitMatch, withConnectionToNodeHost, withHydraCluster)
import Test.Hydra.Tx.Fixture (testNetworkId)
import Test.Hydra.Tx.Gen (genKeyPair)
import Test.QuickCheck (generate)
Expand All @@ -53,13 +53,120 @@ spec :: Spec
spec = around (showLogsOnFailure "HydraClientSpec") $ do
describe "HydraClient on Cardano devnet" $ do
describe "hydra-client" $ do
fit "should filter confirmed UTxO by provided addressed" $ \tracer -> do
it "should filter confirmed UTxO by provided address" $ \tracer -> do
failAfter 60 $
withTempDir "hydra-client" $ \tmpDir ->
filterConfirmedUTxOByAddressScenario tracer tmpDir
it "should filter ALL in confirmed UTxO when given a random address" $ \tracer -> do
failAfter 60 $
withTempDir "hydra-client" $ \tmpDir ->
filterConfirmedUTxOByRandomAddressScenario tracer tmpDir
it "should filter ALL in confirmed UTxO when given a wrong address" $ \tracer -> do
failAfter 60 $
withTempDir "hydra-client" $ \tmpDir ->
filterConfirmedUTxOByWrongAddressScenario tracer tmpDir

filterConfirmedUTxOByAddressScenario :: Tracer IO EndToEndLog -> FilePath -> IO ()
filterConfirmedUTxOByAddressScenario tracer tmpDir = do
scenarioSetup tracer tmpDir $ \node nodes hydraTracer -> do
(expectedSnapshotNumber, (aliceExternalVk, bobExternalVk)) <- prepareScenario node nodes tracer
let [n1, n2, _] = toList nodes

-- 1/ query alice address from alice node
confirmedUTxO1 <- runScenario hydraTracer n1 (textAddrOf aliceExternalVk) $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo /= toJSON (mempty :: Map TxIn Value)
Just utxo

-- 2/ query bob address from bob node
confirmedUTxO2 <- runScenario hydraTracer n2 (textAddrOf bobExternalVk) $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo /= toJSON (mempty :: Map TxIn Value)
Just utxo

confirmedUTxO1 `shouldNotBe` confirmedUTxO2

-- 3/ query bob address from alice node
confirmedUTxO3 <- runScenario hydraTracer n1 (textAddrOf bobExternalVk) $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo /= toJSON (mempty :: Map TxIn Value)
Just utxo

confirmedUTxO2 `shouldBe` confirmedUTxO3

filterConfirmedUTxOByRandomAddressScenario :: Tracer IO EndToEndLog -> FilePath -> IO ()
filterConfirmedUTxOByRandomAddressScenario tracer tmpDir = do
scenarioSetup tracer tmpDir $ \node nodes hydraTracer -> do
(expectedSnapshotNumber, _) <- prepareScenario node nodes tracer
let [n1, _, _] = toList nodes

(randomVk, _) <- generate genKeyPair
runScenario hydraTracer n1 (textAddrOf randomVk) $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo == toJSON (mempty :: Map TxIn Value)

filterConfirmedUTxOByWrongAddressScenario :: Tracer IO EndToEndLog -> FilePath -> IO ()
filterConfirmedUTxOByWrongAddressScenario tracer tmpDir = do
scenarioSetup tracer tmpDir $ \node nodes hydraTracer -> do
(expectedSnapshotNumber, _) <- prepareScenario node nodes tracer
let [_, _, n3] = toList nodes

runScenario hydraTracer n3 "pepe" $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo == toJSON (mempty :: Map TxIn Value)

-- * Helpers
unwrapAddress :: AddressInEra -> Text
unwrapAddress = \case
ShelleyAddressInEra addr -> serialiseToBech32 addr
ByronAddressInEra{} -> error "Byron."

textAddrOf :: VerificationKey PaymentKey -> Text
textAddrOf vk = unwrapAddress (mkVkAddress @Era testNetworkId vk)

queryAddress :: Text -> Text
queryAddress addr = "/?history=yes&address=" <> addr

runScenario ::
Tracer IO HydraNodeLog ->
HydraClient ->
Text ->
(HydraClient -> IO a) ->
IO a
runScenario hydraTracer hnode addr action = do
withConnectionToNodeHost
hydraTracer
(HydraNode.hydraNodeId hnode)
(HydraNode.apiHost hnode)
(Just $ Text.unpack (queryAddress addr))
action

scenarioSetup ::
Tracer IO EndToEndLog ->
FilePath ->
(RunningNode -> NonEmpty HydraClient -> Tracer IO HydraNodeLog -> IO a) ->
IO a
scenarioSetup tracer tmpDir action = do
withCardanoNodeDevnet (contramap FromCardanoNode tracer) tmpDir $ \node@RunningNode{nodeSocket} -> do
aliceKeys@(aliceCardanoVk, _) <- generate genKeyPair
bobKeys@(bobCardanoVk, _) <- generate genKeyPair
Expand All @@ -81,90 +188,51 @@ filterConfirmedUTxOByAddressScenario tracer tmpDir = do
seedFromFaucet_ node bobCardanoVk 100_000_000 (contramap FromFaucet tracer)
seedFromFaucet_ node carolCardanoVk 100_000_000 (contramap FromFaucet tracer)

send n1 $ input "Init" []
headId <-
waitForAllMatch 10 [n1, n2, n3] $
headIsInitializingWith (Set.fromList [alice, bob, carol])

-- Get some UTXOs to commit to a head
(aliceExternalVk, aliceExternalSk) <- generate genKeyPair
committedUTxOByAlice <- seedFromFaucet node aliceExternalVk aliceCommittedToHead (contramap FromFaucet tracer)
requestCommitTx n1 committedUTxOByAlice <&> signTx aliceExternalSk >>= submitTx node

(bobExternalVk, bobExternalSk) <- generate genKeyPair
committedUTxOByBob <- seedFromFaucet node bobExternalVk bobCommittedToHead (contramap FromFaucet tracer)
requestCommitTx n2 committedUTxOByBob <&> signTx bobExternalSk >>= submitTx node

requestCommitTx n3 mempty >>= submitTx node

let u0 = committedUTxOByAlice <> committedUTxOByBob

waitFor hydraTracer 10 [n1, n2, n3] $ output "HeadIsOpen" ["utxo" .= u0, "headId" .= headId]

-- Create an arbitrary transaction using some input.
-- XXX: This makes a scenario where bob has more than 1 output, alice a small one and carol none.
-- NOTE(AB): this is partial and will fail if we are not able to generate a payment
let firstCommittedUTxO = Prelude.head $ UTxO.pairs committedUTxOByAlice
let Right tx =
mkSimpleTx
firstCommittedUTxO
(inHeadAddress bobExternalVk, lovelaceToValue paymentFromAliceToBob)
aliceExternalSk
send n1 $ input "NewTx" ["transaction" .= tx]
waitFor hydraTracer 10 [n1, n2, n3] $
output "TxValid" ["transactionId" .= txId tx, "headId" .= headId]
let expectedSnapshotNumber :: Int = 1

-- 1/ query alice address from alice node
confirmedUTxO1 <- runScenario hydraTracer n1 (textAddrOf aliceExternalVk) $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo /= toJSON (mempty :: Map TxIn Value)
Just utxo

-- 2/ query bob address from bob node
confirmedUTxO2 <- runScenario hydraTracer n2 (textAddrOf bobExternalVk) $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo /= toJSON (mempty :: Map TxIn Value)
Just utxo

confirmedUTxO1 `shouldNotBe` confirmedUTxO2

-- 3/ query bob address from alice node
confirmedUTxO3 <- runScenario hydraTracer n1 (textAddrOf bobExternalVk) $ \con -> do
waitMatch 3 con $ \v -> do
guard $ v ^? key "tag" == Just "SnapshotConfirmed"
snapshotNumber <- v ^? key "snapshot" . key "number"
guard $ snapshotNumber == toJSON expectedSnapshotNumber
utxo <- v ^? key "snapshot" . key "utxo"
guard $ utxo /= toJSON (mempty :: Map TxIn Value)
Just utxo

confirmedUTxO2 `shouldBe` confirmedUTxO3
where
unwrapAddress :: AddressInEra -> Text
unwrapAddress = \case
ShelleyAddressInEra addr -> serialiseToBech32 addr
ByronAddressInEra{} -> error "Byron."

textAddrOf vk = unwrapAddress (mkVkAddress @Era testNetworkId vk)

queryAddress addr = "/?history=yes&address=" <> addr

runScenario hydraTracer hnode addr action = do
withConnectionToNodeHost
hydraTracer
(HydraNode.hydraNodeId hnode)
(HydraNode.apiHost hnode)
(Just $ Text.unpack (queryAddress addr))
action
action node nodes hydraTracer

prepareScenario ::
RunningNode ->
NonEmpty HydraClient ->
Tracer IO EndToEndLog ->
IO (Int, (VerificationKey PaymentKey, VerificationKey PaymentKey))
prepareScenario node nodes tracer = do
let [n1, n2, n3] = toList nodes
let hydraTracer = contramap FromHydraNode tracer

send n1 $ input "Init" []
headId <-
waitForAllMatch 10 [n1, n2, n3] $
headIsInitializingWith (Set.fromList [alice, bob, carol])

-- Get some UTXOs to commit to a head
(aliceExternalVk, aliceExternalSk) <- generate genKeyPair
committedUTxOByAlice <- seedFromFaucet node aliceExternalVk aliceCommittedToHead (contramap FromFaucet tracer)
requestCommitTx n1 committedUTxOByAlice <&> signTx aliceExternalSk >>= submitTx node

(bobExternalVk, bobExternalSk) <- generate genKeyPair
committedUTxOByBob <- seedFromFaucet node bobExternalVk bobCommittedToHead (contramap FromFaucet tracer)
requestCommitTx n2 committedUTxOByBob <&> signTx bobExternalSk >>= submitTx node

requestCommitTx n3 mempty >>= submitTx node

let u0 = committedUTxOByAlice <> committedUTxOByBob

waitFor hydraTracer 10 [n1, n2, n3] $ output "HeadIsOpen" ["utxo" .= u0, "headId" .= headId]

-- Create an arbitrary transaction using some input.
-- XXX: This makes a scenario where bob has more than 1 output, alice a small one and carol none.
-- NOTE(AB): this is partial and will fail if we are not able to generate a payment
let firstCommittedUTxO = Prelude.head $ UTxO.pairs committedUTxOByAlice
let Right tx =
mkSimpleTx
firstCommittedUTxO
(inHeadAddress bobExternalVk, lovelaceToValue paymentFromAliceToBob)
aliceExternalSk
send n1 $ input "NewTx" ["transaction" .= tx]
waitFor hydraTracer 10 [n1, n2, n3] $
output "TxValid" ["transactionId" .= txId tx, "headId" .= headId]
let expectedSnapshotNumber :: Int = 1
pure (expectedSnapshotNumber, (aliceExternalVk, bobExternalVk))

-- * Fixtures

Expand All @@ -177,23 +245,8 @@ bobCommittedToHead = 5_000_000
paymentFromAliceToBob :: Num a => a
paymentFromAliceToBob = 1_000_000

someTxId :: IsString s => s
someTxId = "9fdc525c20bc00d9dfa9d14904b65e01910c0dfe3bb39865523c1e20eaeb0903"

inHeadAddress :: VerificationKey PaymentKey -> AddressInEra
inHeadAddress =
mkVkAddress network
where
network = Testnet (NetworkMagic 14)

-- * Helpers

int :: Int -> Int
int = id

outputRef :: TxId -> Natural -> Value
outputRef tid tix =
object
[ "txId" .= tid
, "index" .= tix
]

0 comments on commit 5c701e2

Please sign in to comment.