Skip to content

Commit

Permalink
bugfixes, end to end offline mode tests
Browse files Browse the repository at this point in the history
  • Loading branch information
cardenaso11 committed Dec 6, 2023
1 parent b39aafb commit 9063377
Show file tree
Hide file tree
Showing 14 changed files with 261 additions and 299 deletions.
2 changes: 0 additions & 2 deletions hydra-cluster/hydra-cluster.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -148,12 +148,10 @@ test-suite tests
other-modules:
Paths_hydra_cluster
Spec
Test.ChainSpec
Test.CardanoClientSpec
Test.CardanoNodeSpec
Test.ChainObserverSpec
Test.DirectChainSpec
Test.OfflineChainSpec
Test.EndToEndSpec
Test.GeneratorSpec
Test.Hydra.Cluster.CardanoCliSpec
Expand Down
3 changes: 2 additions & 1 deletion hydra-cluster/src/Hydra/Cluster/Faucet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,8 +98,9 @@ seedFromFaucet_ ::
seedFromFaucet_ node vk ll tracer =
void $ seedFromFaucet node vk ll tracer

--TODO(Elaine): we probably want a simplified but parallel version of this/createOutputAddress for offline mode , that just constructs a UTxO
-- TODO(Elaine): we probably want a simplified but parallel version of this/createOutputAddress for offline mode , that just constructs a UTxO
-- actually no take a look at seedFromFaucet

-- | Return the remaining funds to the faucet
returnFundsToFaucet ::
Tracer IO FaucetLog ->
Expand Down
121 changes: 97 additions & 24 deletions hydra-cluster/src/Hydra/Cluster/Util.hs
Original file line number Diff line number Diff line change
@@ -1,40 +1,68 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE AllowAmbiguousTypes #-}

{-# LANGUAGE ScopedTypeVariables #-}

-- | Utilities used across hydra-cluster
module Hydra.Cluster.Util where
module Hydra.Cluster.Util (
readConfigFile,
keysFor,
createAndSaveSigningKey,
offlineConfigFor,
offlineConfigForUTxO,
chainConfigFor,
initialUtxoWithFunds,
buildAddress,
) where

import Hydra.Prelude

import Data.Aeson qualified as Aeson
import Data.ByteString qualified as BS
import Data.Map qualified as Map
import Hydra.Cardano.Api (
Address,
AsType (AsPaymentKey, AsSigningKey),
HasTypeProxy (AsType),
Key (VerificationKey, getVerificationKey),
IsCardanoEra,
IsShelleyBasedEra,
Key (VerificationKey, getVerificationKey, verificationKeyHash),
Lovelace,
NetworkId,
PaymentKey,
SigningKey,
ShelleyAddr,
SigningKey (GenesisUTxOSigningKey, PaymentSigningKey),
SocketPath,
StakeAddressReference (NoStakeAddress),
TextEnvelopeError (TextEnvelopeAesonDecodeError),
Tx,
TxOutValue (TxOutValue),
UTxO' (UTxO),
VerificationKey (GenesisUTxOVerificationKey, PaymentVerificationKey),
castSigningKey,
castVerificationKey,
deserialiseFromTextEnvelope,
genesisUTxOPseudoTxIn,
lovelaceToTxOutValue,
mkTxOutValue,
shelleyAddressInEra,
textEnvelopeToJSON,
)
import Hydra.Cardano.Api.MultiAssetSupportedInEra (HasMultiAsset)
import Hydra.Cardano.Api.Prelude (PaymentCredential (PaymentCredentialByKey), ReferenceScript (ReferenceScriptNone), TxOut (TxOut), TxOutDatum (TxOutDatumNone), Value, lovelaceToTxOutValue, makeShelleyAddress, shelleyAddressInEra)
import Hydra.Chain (ChainEvent, OnChainTx (OnInitTx, contestationPeriod, parties), PostChainTx)
import Hydra.Cluster.Fixture (Actor, actorName)
import Hydra.ContestationPeriod (ContestationPeriod)
import Hydra.Ledger (IsTx (UTxOType))
import Hydra.Ledger.Cardano (genSigningKey)
import Hydra.Options (ChainConfig (..), defaultChainConfig)
import Hydra.Options (ChainConfig (..), OfflineConfig (OfflineConfig, initialUTxOFile, ledgerGenesisFile), defaultChainConfig)
import Hydra.Party (Party)
import Paths_hydra_cluster qualified as Pkg
import System.FilePath ((<.>), (</>))
import Test.Hydra.Prelude (failure, Expectation, shouldBe)
import Test.Hydra.Prelude (Expectation, failure, shouldBe)
import Test.QuickCheck (generate)
import Hydra.Chain (PostChainTx)
import Hydra.Chain (ChainEvent)
import Hydra.Ledger (IsTx)
import Hydra.Party (Party)
import Hydra.Chain (OnChainTx(OnInitTx, contestationPeriod, parties))
import Hydra.Ledger (IsTx(UTxOType))

-- import CardanoClient (buildAddress)

-- | Lookup a config file similar reading a file from disk.
-- If the env variable `HYDRA_CONFIG_DIR` is set, filenames will be
Expand Down Expand Up @@ -70,6 +98,62 @@ createAndSaveSigningKey path = do
writeFileLBS path $ textEnvelopeToJSON (Just "Key used to commit funds into a Head") sk
pure sk

offlineConfigFor :: [(Actor, Value)] -> FilePath -> NetworkId -> IO OfflineConfig
offlineConfigFor actorToVal targetDir networkId = do
initialUtxoForActors actorToVal networkId >>= offlineConfigForUTxO @Tx targetDir

offlineConfigForUTxO :: forall tx. IsTx tx => FilePath -> UTxOType tx -> IO OfflineConfig
offlineConfigForUTxO targetDir utxo = do
utxoPath <- seedInitialUTxOFromOffline @tx targetDir utxo
pure $
OfflineConfig
{ initialUTxOFile = utxoPath
, ledgerGenesisFile = Nothing
}

seedInitialUTxOFromOffline :: IsTx tx => FilePath -> UTxOType tx -> IO FilePath
seedInitialUTxOFromOffline targetDir utxo = do
let destinationPath = targetDir </> "utxo.json"
writeFileBS destinationPath . toStrict . Aeson.encode $ utxo

-- Aeson.throwDecodeStrict =<< readFileBS (targetDir </> "utxo.json")
pure destinationPath

buildAddress :: VerificationKey PaymentKey -> NetworkId -> Address ShelleyAddr
buildAddress vKey networkId =
makeShelleyAddress networkId (PaymentCredentialByKey $ verificationKeyHash vKey) NoStakeAddress

initialUtxoWithFunds ::
forall era ctx.
(IsShelleyBasedEra era, HasMultiAsset era) =>
NetworkId ->
[(VerificationKey PaymentKey, Value)] ->
IO (UTxO' (TxOut ctx era))
initialUtxoWithFunds networkId valueMap =
pure
. UTxO
. Map.fromList
. map (\(vKey, val) -> (txin vKey, txout vKey val))
$ valueMap
where
txout vKey val =
TxOut
(shelleyAddressInEra @era $ buildAddress vKey networkId)
(mkTxOutValue val)
TxOutDatumNone
ReferenceScriptNone
txin vKey = genesisUTxOPseudoTxIn networkId (verificationKeyHash . castKey $ vKey)
castKey (PaymentVerificationKey vkey) = GenesisUTxOVerificationKey vkey

initialUtxoForActors :: [(Actor, Value)] -> NetworkId -> IO (UTxOType Tx)
initialUtxoForActors actorToVal networkId = do
initialUtxoWithFunds networkId =<< vkToVal
where
vkForActor actor = fmap fst (keysFor actor)
vkToVal =
forM actorToVal $ \(actor, val) ->
vkForActor actor <&> (,val)

chainConfigFor :: HasCallStack => Actor -> FilePath -> SocketPath -> [Actor] -> ContestationPeriod -> IO ChainConfig
chainConfigFor me targetDir nodeSocket them cp = do
when (me `elem` them) $
Expand All @@ -91,14 +175,3 @@ chainConfigFor me targetDir nodeSocket them cp = do
vkTarget x = targetDir </> vkName x
skName x = actorName x <.> ".sk"
vkName x = actorName x <.> ".vk"

seedInitialUTxOFromOffline :: IsTx tx => UTxOType tx -> FilePath -> IO ()
seedInitialUTxOFromOffline utxo targetDir = do
-- i assume a static file might be too rigid ? we can keep around constants and then write them to disk for each test
-- readConfigFile "initial-utxo.json" >>= writeFileBS (targetDir </> "initial-utxo.json")

writeFileBS (targetDir </> "utxo.json") . toStrict . Aeson.encode $ utxo

-- Aeson.throwDecodeStrict =<< readFileBS (targetDir </> "utxo.json")
pure ()

83 changes: 37 additions & 46 deletions hydra-cluster/src/HydraNode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,10 +25,11 @@ import Hydra.Ledger.Cardano ()
import Hydra.Logging (Tracer, Verbosity (..), traceWith)
import Hydra.Network (Host (Host), NodeId (NodeId))
import Hydra.Network qualified as Network
import Hydra.Options (ChainConfig (..), LedgerConfig (..), RunOptions (..), defaultChainConfig, toArgs)
import Hydra.Options (ChainConfig (..), LedgerConfig (..), OfflineConfig, RunOptions (..), defaultChainConfig, toArgs)
import Network.HTTP.Req (GET (..), HttpException, JsonResponse, NoReqBody (..), POST (..), ReqBodyJson (..), defaultHttpConfig, responseBody, runReq, (/:))
import Network.HTTP.Req qualified as Req
import Network.WebSockets (Connection, receiveData, runClient, sendClose, sendTextData)
import System.Directory (createDirectoryIfMissing)
import System.FilePath ((<.>), (</>))
import System.IO.Temp (withSystemTempDirectory)
import System.Process (
Expand All @@ -40,7 +41,6 @@ import System.Process (
)
import Test.Hydra.Prelude (checkProcessHasNotDied, failAfter, failure, withLogFile)
import Prelude qualified
import Hydra.Options (OfflineConfig)

data HydraClient = HydraClient
{ hydraNodeId :: Int
Expand Down Expand Up @@ -201,20 +201,6 @@ data HydraNodeLog
deriving stock (Eq, Show, Generic)
deriving anyclass (ToJSON, FromJSON, ToObject)

-- run a single hydra node in offline mode
-- withHydraClusterOffline ::
-- HasCallStack =>
-- Tracer IO EndToEndLog ->
-- FilePath ->
-- -- (VerificationKey PaymentKey, SigningKey PaymentKey) ->
-- SigningKey HydraKey ->
-- ContestationPeriod ->
-- (HydraClient -> IO a) ->
-- IO a
-- withHydraClusterOffline tracer workDir hydraKey contestationPeriod action =
-- withConfiguredHydraCluster tracer workDir "" firstNodeId allKeys hydraKeys ("9fdc525c20bc00d9dfa9d14904b65e01910c0dfe3bb39865523c1e20eaeb0903") (const $ id) contestationPeriod action
-- NOTE(Elaine): txid constant taken from EndToEndSpec someTxId, lift the whole cyclic dependency thing

-- XXX: The two lists need to be of same length. Also the verification keys can
-- be derived from the signing keys.
withHydraCluster ::
Expand Down Expand Up @@ -296,18 +282,18 @@ withConfiguredHydraCluster tracer workDir nodeSocket firstNodeId allKeys hydraKe
hydraScriptsTxId
(\c -> startNodes (c : clients) rest)

withOfflineHydraNode ::
Tracer IO EndToEndLog
-> OfflineConfig
-> FilePath
-> Int
-> SigningKey HydraKey
-> (HydraClient -> IO a)
-> IO a
withOfflineHydraNode ::
Tracer IO HydraNodeLog ->
OfflineConfig ->
FilePath ->
Int ->
SigningKey HydraKey ->
(HydraClient -> IO a) ->
IO a
withOfflineHydraNode tracer offlineConfig workDir hydraNodeId hydraSKey action =
withLogFile logFilePath $ \logFileHandle -> do
withOfflineHydraNode' tracer offlineConfig workDir hydraNodeId hydraSKey (Just logFileHandle) $ do
\_ _err processHandle -> do
withOfflineHydraNode' offlineConfig workDir hydraNodeId hydraSKey (Just logFileHandle) $ do
\_stdoutHandle _stderrHandle processHandle -> do
result <-
race
(checkProcessHasNotDied ("hydra-node (" <> show hydraNodeId <> ")") processHandle)
Expand All @@ -318,19 +304,24 @@ withOfflineHydraNode tracer offlineConfig workDir hydraNodeId hydraSKey action =
where
logFilePath = workDir </> "logs" </> "hydra-node-" <> show hydraNodeId <.> "log"

withPersistentDirectoryDebug :: MonadIO m => FilePath -> (FilePath -> m a) -> m a
withPersistentDirectoryDebug name action = do
liftIO $ createDirectoryIfMissing True name
putStrLn $ "Persistent Directory Created: " <> name
action name

withOfflineHydraNode' ::
Tracer IO EndToEndLog
-> OfflineConfig
-> FilePath
-> Int
-> SigningKey HydraKey
OfflineConfig ->
FilePath ->
Int ->
SigningKey HydraKey ->
-- | If given use this as std out.
-> Maybe Handle
Maybe Handle ->
-- -> (HydraClient -> IO a)
-> (Handle -> Handle -> ProcessHandle -> IO a)
-> IO a
withOfflineHydraNode' tracer offlineConfig workDir hydraNodeId hydraSKey mGivenStdOut action =
withSystemTempDirectory "hydra-node" $ \dir -> do
(Handle -> Handle -> ProcessHandle -> IO a) ->
IO a
withOfflineHydraNode' offlineConfig workDir hydraNodeId hydraSKey mGivenStdOut action =
withPersistentDirectoryDebug "hydra-node-tempdir" $ \dir -> do
let cardanoLedgerProtocolParametersFile = dir </> "protocol-parameters.json"
readConfigFile "protocol-parameters.json" >>= writeFileBS cardanoLedgerProtocolParametersFile
let hydraSigningKey = dir </> (show hydraNodeId <> ".sk")
Expand All @@ -340,12 +331,14 @@ withOfflineHydraNode' tracer offlineConfig workDir hydraNodeId hydraSKey mGivenS
{ cardanoLedgerProtocolParametersFile
}
let p =
-- ( hydraNodeProcess . (\args -> trace ("ARGS DUMP: " <> foldMap (" "<>) (toArgs args)) args) $
( hydraNodeProcess $
RunOptions
{ verbosity = Verbose "HydraNode"
, nodeId = NodeId $ show hydraNodeId
, host = "127.0.0.1"
, port = fromIntegral $ 5_000 + hydraNodeId
, -- NOTE(Elaine): port 5000 is used on recent versions of macos
port = fromIntegral $ 5_100 + hydraNodeId
, peers
, apiHost = "127.0.0.1"
, apiPort = fromIntegral $ 4_000 + hydraNodeId
Expand Down Expand Up @@ -373,7 +366,7 @@ withOfflineHydraNode' tracer offlineConfig workDir hydraNodeId hydraSKey mGivenS
-- | Run a hydra-node with given 'ChainConfig' and using the config from
-- config/.
withHydraNode ::
Tracer IO EndToEndLog ->
Tracer IO HydraNodeLog ->
ChainConfig ->
FilePath ->
Int ->
Expand All @@ -395,11 +388,9 @@ withHydraNode tracer chainConfig workDir hydraNodeId hydraSKey hydraVKeys allNod
where
logFilePath = workDir </> "logs" </> "hydra-node-" <> show hydraNodeId <.> "log"


-- | Run a hydra-node with given 'ChainConfig' and using the config from
-- config/.
withHydraNode' ::
-- Either OfflineConfig ChainConfig ->
ChainConfig ->
FilePath ->
Int ->
Expand Down Expand Up @@ -431,7 +422,7 @@ withHydraNode' chainConfig workDir hydraNodeId hydraSKey hydraVKeys allNodeIds h
{ verbosity = Verbose "HydraNode"
, nodeId = NodeId $ show hydraNodeId
, host = "127.0.0.1"
, port = fromIntegral $ 5_000 + hydraNodeId
, port = fromIntegral $ 5_100 + hydraNodeId
, peers
, apiHost = "127.0.0.1"
, apiPort = fromIntegral $ 4_000 + hydraNodeId
Expand All @@ -440,11 +431,11 @@ withHydraNode' chainConfig workDir hydraNodeId hydraSKey hydraVKeys allNodeIds h
, hydraVerificationKeys
, hydraScriptsTxId
, persistenceDir = workDir </> "state-" <> show hydraNodeId
-- , chainConfig = fromRight defaultChainConfig chainConfig
, chainConfig
, -- , chainConfig = fromRight defaultChainConfig chainConfig
chainConfig
, ledgerConfig
-- , offlineConfig = leftToMaybe chainConfig
, offlineConfig = Nothing
, -- , offlineConfig = leftToMaybe chainConfig
offlineConfig = Nothing
}
)
{ std_out = maybe CreatePipe UseHandle mGivenStdOut
Expand All @@ -459,7 +450,7 @@ withHydraNode' chainConfig workDir hydraNodeId hydraSKey hydraVKeys allNodeIds h
peers =
[ Host
{ Network.hostname = "127.0.0.1"
, Network.port = fromIntegral $ 5_000 + i
, Network.port = fromIntegral $ 5_100 + i
}
| i <- allNodeIds
, i /= hydraNodeId
Expand Down
36 changes: 0 additions & 36 deletions hydra-cluster/test/Test/ChainSpec.hs

This file was deleted.

Loading

0 comments on commit 9063377

Please sign in to comment.