diff --git a/exe/Main.hs b/exe/Main.hs index d4096ff..de45aed 100644 --- a/exe/Main.hs +++ b/exe/Main.hs @@ -2,7 +2,7 @@ module Main where import Control.Concurrent (threadDelay) import Control.Monad (forever) -import Pegasus (RunningNode (..), withCardanoNodeDevnet) +import Pegasus (Devnet (..), withCardanoNodeDevnet) import System.IO (BufferMode (..), hSetBuffering, stdout) import Text.Pretty.Simple (pPrint) diff --git a/src/Pegasus.hs b/src/Pegasus.hs index 22833b5..df21510 100644 --- a/src/Pegasus.hs +++ b/src/Pegasus.hs @@ -32,7 +32,7 @@ import System.IO qualified import System.Posix (Handler (Catch), installHandler, ownerReadMode, setFileMode, sigTERM) import System.Process.Typed (setStdout, stopProcess, useHandleClose, waitExitCode, withProcessWait) -data RunningNode = RunningNode +data Devnet = Devnet { nodeVersion :: Text , nodeSocket :: SocketPath , logFile :: FilePath @@ -47,7 +47,7 @@ withCardanoNodeDevnet :: -- | Directory to persist logs and any state. FilePath -> -- | Callback when network started. - (RunningNode -> IO ()) -> + (Devnet -> IO ()) -> IO () withCardanoNodeDevnet dir cont = do cleanup @@ -68,7 +68,7 @@ withCardanoNodeDevnet dir cont = do let socketPath = File $ dir nodeSocket waitForSocket socketPath cont - RunningNode + Devnet { nodeVersion , nodeSocket = socketPath , logFile diff --git a/test/Main.hs b/test/Main.hs index 4da8d49..9deecf9 100644 --- a/test/Main.hs +++ b/test/Main.hs @@ -9,8 +9,8 @@ import Data.ByteString qualified as BS import Data.ByteString.Char8 qualified as BS8 import Data.Function ((&)) import Data.Time (NominalDiffTime) -import Lens.Micro ((^?)) -import Lens.Micro.Aeson (key, _Number) +import Lens.Micro ((^..), (^?)) +import Lens.Micro.Aeson (key, members, _Number) import System.Process.Typed ( ExitCode (..), byteStringOutput, @@ -29,7 +29,7 @@ import System.Process.Typed ( ) import System.Timeout (timeout) import Test.HUnit (assertFailure) -import Test.Hspec (HasCallStack, Spec, hspec, it, shouldReturn, shouldSatisfy) +import Test.Hspec (HasCallStack, Spec, hspec, it, shouldNotBe, shouldReturn, shouldSatisfy) main :: IO () main = hspec spec @@ -44,10 +44,14 @@ testStartsDevnetWithin1Second :: IO () testStartsDevnetWithin1Second = withProcessTerm cmd $ \p -> do failAfter 1 $ waitUntilReady p + -- Devnet should produce blocks b1 <- cliQueryBlock threadDelay 100_000 -- TODO: configurable block time b2 <- cliQueryBlock b2 `shouldSatisfy` (> b1) + -- Devnet should contain some UTxO + utxo <- cliQueryUTxOList + utxo `shouldNotBe` [] where waitUntilReady p = do t <- BS8.hGetLine (getStdout p) @@ -64,6 +68,10 @@ testStartsDevnetWithin1Second = out <- readProcessStdout_ (shell "./tmp-pegasus/bin/cardano-cli query tip --testnet-magic 42 --socket-path tmp-pegasus/node.socket") pure $ out ^? key "block" . _Number + cliQueryUTxOList = do + out <- readProcessStdout_ (shell "./tmp-pegasus/bin/cardano-cli query utxo --whole-utxo --output-json --testnet-magic 42 --socket-path tmp-pegasus/node.socket") + pure $ out ^.. members + testCardanoNodeEmbed :: IO () testCardanoNodeEmbed = do withProcessTerm cmd $ \_ -> do