Skip to content

Commit

Permalink
back to cardano-wallet cluster launcher
Browse files Browse the repository at this point in the history
  • Loading branch information
mikekeke committed Nov 2, 2022
1 parent efb8aba commit 8e26b47
Show file tree
Hide file tree
Showing 13 changed files with 143 additions and 98 deletions.
17 changes: 10 additions & 7 deletions contract-execution/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,8 @@ import Data.Monoid (Last (getLast))
import Data.Text.Lazy qualified as T
import ExampleContracts (ownValueToState)
import Test.Plutip.Config (
PlutipConfig (extraConfig),
-- PlutipConfig (extraConfig),
PlutipConfig,
)
import Test.Plutip.Contract (runContract)
import Test.Plutip.Internal.BotPlutusInterface.Wallet (
Expand All @@ -20,9 +21,10 @@ import Test.Plutip.Internal.BotPlutusInterface.Wallet (
mkMainnetAddress,
walletPkh,
)
import Test.Plutip.Internal.Cluster.Extra.Types (
ExtraConfig (ecSlotLength),
)

-- import Test.Plutip.Internal.Cluster.Extra.Types (
-- ExtraConfig (ecSlotLength),
-- )
import Test.Plutip.Internal.LocalCluster (
startCluster,
stopCluster,
Expand All @@ -38,12 +40,13 @@ import Text.Pretty.Simple (pShow)
main :: IO ()
main = do
let slotLen = 1
extraConf = def {ecSlotLength = slotLen}
plutipConfig = def {extraConfig = extraConf}
-- extraConf = def {ecSlotLength = slotLen}
-- plutipConfig = def {extraConfig = extraConf}
plutipConfig = def

putStrLn "Starting cluster..."
(st, _) <- startCluster plutipConfig $ do
w <- addSomeWallet [toAda 10]
w <- addSomeWallet [toAda 100]
liftIO $ putStrLn "Waiting for wallets to be funded..."
CI.awaitWalletFunded w slotLen

Expand Down
5 changes: 5 additions & 0 deletions debug
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
Pool IDs:
[INFO] 2022-11-02T12:40:41.336Z [(PoolPubKeyHash (Ed25519KeyHash (unsafePartial $ fromJust $ ed25519KeyHashFromBech32 (Just "pool1k3tk3sdzmf9az04u4g0229qgak33mnppwewvh4q8ek5ly09nqjm")))),(PoolPubKeyHash (Ed25519KeyHash (unsafePartial $ fromJust $ ed25519KeyHashFromBech32 (Just "pool1hvg5evmawhaq2fsr9rprtg76u226x0gt5e62t6c78etgu2j7xtn")))),(PoolPubKeyHash (Ed25519KeyHash (unsafePartial $ fromJust $ ed25519KeyHashFromBech32 (Just "pool1as50x0wtumtyqzs7tceeh5ry0syh8jnvpnuu9wlxswxuv48sw4w"))))]
[INFO] 2022-11-02T12:40:41.343Z { cost: fromString "0", margin: { denominator: fromString "10", numerator: fromString "1" }, operator: (PoolPubKeyHash (Ed25519KeyHash (unsafePartial $ fromJust $ ed25519KeyHashFromBech32 (Just "pool1k3tk3sdzmf9az04u4g0229qgak33mnppwewvh4q8ek5ly09nqjm")))), pledge: fromString "100000000000000", poolMetadata: (Just (PoolMetadata { hash: (PoolMetadataHash (hexToByteArrayUnsafe "e72e33850e9c630b65366e3ce562370cd302674f111bfff74b0a5f3dd7f60ca1")), url: (URL "http://localhost:42601/3.json") })), poolOwners: [(PaymentPubKeyHash (PubKeyHash (Ed25519KeyHash 0a334ab6b5301fc0b1c71a5c9606750f182ac9e302539081e9548eae)))], relays: [], rewardAccount: (RewardAddress (Address stake1uy9rxj4kk5cpls93cud9e9sxw583s2kfuvp98yypa92gats27sp2v)), vrfKeyhash: (VRFKeyHash "4cafd732fef7a0949cc5257600e30c45d0def16128fe578ee01b4ec368536944") }
[INFO] 2022-11-02T12:40:41.347Z { cost: fromString "0", margin: { denominator: fromString "10", numerator: fromString "1" }, operator: (PoolPubKeyHash (Ed25519KeyHash (unsafePartial $ fromJust $ ed25519KeyHashFromBech32 (Just "pool1hvg5evmawhaq2fsr9rprtg76u226x0gt5e62t6c78etgu2j7xtn")))), pledge: fromString "100000000000000", poolMetadata: (Just (PoolMetadata { hash: (PoolMetadataHash (hexToByteArrayUnsafe "e376f46c67a310b399fa5ff8b7b9727556ea454a8c082dedfc9935c2c3fe6ec5")), url: (URL "http://localhost:42601/4.json") })), poolOwners: [(PaymentPubKeyHash (PubKeyHash (Ed25519KeyHash c950caf90326501a1aeed906793fcbb7f3cf5be3d93f6cf156ea1290)))], relays: [], rewardAccount: (RewardAddress (Address stake1u8y4pjheqvn9qxs6amvsv7flewml8n6mu0vn7m832m4p9yqrmpzfw)), vrfKeyhash: (VRFKeyHash "a60460696022af8fdf1d0c68bc007d2ce0b4518bf922f29081187c326f63955f") }
[INFO] 2022-11-02T12:40:41.352Z { cost: fromString "0", margin: { denominator: fromString "10", numerator: fromString "1" }, operator: (PoolPubKeyHash (Ed25519KeyHash (unsafePartial $ fromJust $ ed25519KeyHashFromBech32 (Just "pool1as50x0wtumtyqzs7tceeh5ry0syh8jnvpnuu9wlxswxuv48sw4w")))), pledge: fromString "200000000000000", poolMetadata: (Just (PoolMetadata { hash: (PoolMetadataHash (hexToByteArrayUnsafe "ef41266d9fad1f81480575231b735d75a483d5b03e5e5e67da5f07cd30c7c246")), url: (URL "http://localhost:42601/1.json") })), poolOwners: [(PaymentPubKeyHash (PubKeyHash (Ed25519KeyHash 7235e82c96f4b931558ce2df1273b8eeba306b103aa78bc13c5a0ca8)))], relays: [], rewardAccount: (RewardAddress (Address stake1u9ert6pvjm6tjv243n3d7ynnhrht5vrtzqa20z7p83dqe2qgl74xn)), vrfKeyhash: (VRFKeyHash "63e3374aeb64ee7c6ad51e0ba1c3edd2f2a048a23f3b07d6ce0af66b19aa9942") }
18 changes: 11 additions & 7 deletions local-cluster/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,17 +19,19 @@ import Options.Applicative (Parser, helper, info)
import Options.Applicative qualified as Options
import Test.Plutip.Config (
ChainIndexMode (CustomPort, DefaultPort, NotNeeded),
PlutipConfig (chainIndexMode, clusterWorkingDir, extraConfig),
-- PlutipConfig (chainIndexMode, clusterWorkingDir, extraConfig),
PlutipConfig (chainIndexMode, clusterWorkingDir),
WorkingDirectory (Fixed, Temporary),
)
import Test.Plutip.Internal.BotPlutusInterface.Wallet (
addSomeWalletDir,
cardanoMainnetAddress,
walletPkh,
)
import Test.Plutip.Internal.Cluster.Extra.Types (
ExtraConfig (ExtraConfig),
)

-- import Test.Plutip.Internal.Cluster.Extra.Types (
-- ExtraConfig (ExtraConfig),
-- )
import Test.Plutip.Internal.Types (nodeSocket)
import Test.Plutip.LocalCluster (
mkMainnetAddress,
Expand All @@ -44,11 +46,13 @@ main = do
case totalAmount config of
Left e -> error e
Right amt -> do
let ClusterConfig {numWallets, dirWallets, numUtxos, workDir, slotLength, epochSize, cIndexMode} = config
-- let ClusterConfig {numWallets, dirWallets, numUtxos, workDir, slotLength, epochSize, cIndexMode} = config
let ClusterConfig {numWallets, dirWallets, numUtxos, workDir, slotLength, cIndexMode} = config
workingDir = maybe Temporary (`Fixed` False) workDir

extraConf = ExtraConfig slotLength epochSize
plutipConfig = def {clusterWorkingDir = workingDir, extraConfig = extraConf, chainIndexMode = cIndexMode}
-- extraConf = ExtraConfig slotLength epochSize
-- plutipConfig = def {clusterWorkingDir = workingDir, extraConfig = extraConf, chainIndexMode = cIndexMode}
plutipConfig = def {clusterWorkingDir = workingDir, chainIndexMode = cIndexMode}

putStrLn "Starting cluster..."
(st, _) <- startCluster plutipConfig $ do
Expand Down
19 changes: 12 additions & 7 deletions plutip-server/Api/Handlers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ import System.Directory (doesFileExist)
import System.FilePath (replaceFileName)
import Test.Plutip.Config (
ChainIndexMode (NotNeeded),
PlutipConfig (extraConfig),
-- PlutipConfig (extraConfig),
PlutipConfig,
chainIndexMode,
relayNodeLogs,
)
Expand All @@ -32,10 +33,11 @@ import Test.Plutip.Internal.BotPlutusInterface.Wallet (
addSomeWallet,
cardanoMainnetAddress,
)
import Test.Plutip.Internal.Cluster (RunningNode (RunningNode))
import Test.Plutip.Internal.Cluster.Extra.Types (ExtraConfig (ExtraConfig, ecSlotLength))

-- import Test.Plutip.Internal.Cluster (RunningNode (RunningNode))
-- import Test.Plutip.Internal.Cluster.Extra.Types (ExtraConfig (ExtraConfig, ecSlotLength))
import Test.Plutip.Internal.LocalCluster (startCluster, stopCluster)
import Test.Plutip.Internal.Types (ClusterEnv (plutipConf, runningNode))
import Test.Plutip.Internal.Types (ClusterEnv (plutipConf, runningNode), RunningNode(RunningNode))
import Types (
AppM,
ClusterStartupFailureReason (
Expand Down Expand Up @@ -80,8 +82,10 @@ startClusterHandler
statusMVar <- asks status
isClusterDown <- liftIO $ isEmptyMVar statusMVar
unless isClusterDown $ throwError ClusterIsRunningAlready
let extraConf = ExtraConfig slotLength epochSize
cfg = def {relayNodeLogs = nodeLogs, chainIndexMode = NotNeeded, extraConfig = extraConf}
let
-- extraConf = ExtraConfig slotLength epochSize
-- cfg = def {relayNodeLogs = nodeLogs, chainIndexMode = NotNeeded, extraConfig = extraConf}
cfg = def {relayNodeLogs = nodeLogs, chainIndexMode = NotNeeded}

(statusTVar, res@(clusterEnv, _)) <- liftIO $ startCluster cfg setup
liftIO $ putMVar statusMVar statusTVar
Expand All @@ -104,7 +108,8 @@ startClusterHandler
for keysToGenerate $ \lovelaceAmounts -> do
addSomeWallet (fromInteger . unLovelace <$> lovelaceAmounts)
liftIO $ putStrLn "Waiting for wallets to be funded..."
awaitFunds wallets (ecSlotLength $ extraConfig $ plutipConf env)
-- awaitFunds wallets (ecSlotLength $ extraConfig $ plutipConf env)
awaitFunds wallets 0.2
pure (env, wallets)
getNodeSocketFile (runningNode -> RunningNode conn _ _ _) = nodeSocketFile conn
getNodeConfigFile =
Expand Down
11 changes: 6 additions & 5 deletions src/Test/Plutip/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,8 @@ import Cardano.Api (PaymentKey, SigningKey)
import Data.Default (Default, def)
import GHC.Generics (Generic)
import GHC.Natural (Natural)
import Test.Plutip.Internal.Cluster.Extra.Types (ExtraConfig)

-- import Test.Plutip.Internal.Cluster.Extra.Types (ExtraConfig)

-- | Configuration for the cluster working directory
-- This determines where the node database, chain-index database,
Expand Down Expand Up @@ -46,9 +47,9 @@ data PlutipConfig = PlutipConfig
, -- | Any extra pre-determined signers to use.
-- Either provided by a path to the signing key file, or by the signing key itself.
extraSigners :: [Either FilePath (SigningKey PaymentKey)]
, -- | Extra config to set (at the moment) slot lenght and epoch size
-- for local network
extraConfig :: ExtraConfig
-- , -- | Extra config to set (at the moment) slot lenght and epoch size
-- -- for local network
-- extraConfig :: ExtraConfig
}
deriving stock (Generic, Show)

Expand All @@ -64,4 +65,4 @@ data ChainIndexMode
deriving stock (Generic, Eq, Show)

instance Default PlutipConfig where
def = PlutipConfig Nothing Nothing DefaultPort 1 Temporary [] def
def = PlutipConfig Nothing Nothing DefaultPort 1 Temporary [] -- def
9 changes: 5 additions & 4 deletions src/Test/Plutip/Internal/BotPlutusInterface/Wallet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,13 +15,14 @@ import Cardano.Api qualified as CAPI
import Cardano.BM.Data.Tracer (nullTracer)
import Cardano.Wallet.Primitive.Types.Coin (Coin (Coin))

-- import Cardano.Wallet.Shelley.Launch.Cluster (
-- sendFaucetFundsTo,
-- )
import Test.Plutip.Internal.Cluster (
import Cardano.Wallet.Shelley.Launch.Cluster (
sendFaucetFundsTo,
)

-- import Test.Plutip.Internal.Cluster (
-- sendFaucetFundsTo,
-- )

import Control.Arrow (ArrowChoice (left))
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO, liftIO)
Expand Down
77 changes: 39 additions & 38 deletions src/Test/Plutip/Internal/Cluster.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@
{-# OPTIONS_GHC -Wwarn=incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wwarn=missing-deriving-strategies #-}
{-# OPTIONS_GHC -Wwarn=name-shadowing #-}
{-# OPTIONS_GHC -Wwarn=unused-top-binds #-}

-- |
-- This module is modified copy of https://github.com/input-output-hk/cardano-wallet/blob/1952de13f1cd954514cfa1cb02e628cfc9fde675/lib/shelley/src/Cardano/Wallet/Shelley/Launch/Cluster.hs
Expand All @@ -37,44 +38,44 @@

module Test.Plutip.Internal.Cluster
( -- * Local test cluster launcher
withCluster
, LocalClusterConfig (..)
, localClusterConfigFromEnv
, ClusterEra (..)

-- * Node launcher
, NodeParams (..)
, singleNodeParams
, RunningNode (..)

-- * Cluster node launcher
, defaultPoolConfigs
, clusterEraFromEnv
, clusterToApiEra
, clusterEraToString
, withSMASH

-- * Configuration
, LogFileConfig (..)
, logFileConfigFromEnv
, minSeverityFromEnv
, nodeMinSeverityFromEnv
, walletMinSeverityFromEnv
, testMinSeverityFromEnv
, testLogDirFromEnv
, walletListenFromEnv
, tokenMetadataServerFromEnv

-- * Faucets
, Credential (..)
, sendFaucetFundsTo
, sendFaucetAssetsTo
, moveInstantaneousRewardsTo
, oneMillionAda
, genMonetaryPolicyScript

-- * Logging
, ClusterLog (..)
-- withCluster
-- , LocalClusterConfig (..)
-- , localClusterConfigFromEnv
-- , ClusterEra (..)

-- -- * Node launcher
-- , NodeParams (..)
-- , singleNodeParams
-- , RunningNode (..)

-- -- * Cluster node launcher
-- , defaultPoolConfigs
-- , clusterEraFromEnv
-- , clusterToApiEra
-- , clusterEraToString
-- , withSMASH

-- -- * Configuration
-- , LogFileConfig (..)
-- , logFileConfigFromEnv
-- , minSeverityFromEnv
-- , nodeMinSeverityFromEnv
-- , walletMinSeverityFromEnv
-- , testMinSeverityFromEnv
-- , testLogDirFromEnv
-- , walletListenFromEnv
-- , tokenMetadataServerFromEnv

-- -- * Faucets
-- , Credential (..)
-- , sendFaucetFundsTo
-- , sendFaucetAssetsTo
-- , moveInstantaneousRewardsTo
-- , oneMillionAda
-- , genMonetaryPolicyScript

-- -- * Logging
-- , ClusterLog (..)
) where

import Prelude
Expand Down
19 changes: 10 additions & 9 deletions src/Test/Plutip/Internal/Cluster/Extra/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,13 @@
module Test.Plutip.Internal.Cluster.Extra.Utils (
localClusterConfigWithExtraConf,
) where
) where

import Test.Plutip.Internal.Cluster (LocalClusterConfig (LocalClusterConfig), clusterEraFromEnv, clusterEraToString, defaultPoolConfigs, logFileConfigFromEnv)
import Test.Plutip.Internal.Cluster.Extra.Types (ExtraConfig)
-- localClusterConfigWithExtraConf,

localClusterConfigWithExtraConf :: ExtraConfig -> IO LocalClusterConfig
localClusterConfigWithExtraConf ec = do
era <- clusterEraFromEnv
logConf <- logFileConfigFromEnv (Just $ clusterEraToString era)
pure $ LocalClusterConfig defaultPoolConfigs era logConf ec
-- import Test.Plutip.Internal.Cluster (LocalClusterConfig (LocalClusterConfig), clusterEraFromEnv, clusterEraToString, defaultPoolConfigs, logFileConfigFromEnv)
-- import Test.Plutip.Internal.Cluster.Extra.Types (ExtraConfig)

-- localClusterConfigWithExtraConf :: ExtraConfig -> IO LocalClusterConfig
-- localClusterConfigWithExtraConf ec = do
-- era <- clusterEraFromEnv
-- logConf <- logFileConfigFromEnv (Just $ clusterEraToString era)
-- pure $ LocalClusterConfig defaultPoolConfigs era logConf ec
39 changes: 27 additions & 12 deletions src/Test/Plutip/Internal/LocalCluster.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,13 @@ import Cardano.Startup (installSignalHandlers, setDefaultFilePermissions, withUt
import Cardano.Wallet.Logging (stdoutTextTracer, trMessageText)
import Cardano.Wallet.Shelley.Launch (TempDirLog, withSystemTempDir)

-- import Cardano.Wallet.Shelley.Launch.Cluster (ClusterLog, localClusterConfigFromEnv, testMinSeverityFromEnv, walletMinSeverityFromEnv, withCluster)
import Cardano.Wallet.Shelley.Launch.Cluster (
ClusterLog,
localClusterConfigFromEnv,
testMinSeverityFromEnv,
walletMinSeverityFromEnv,
withCluster,
)

import Control.Monad (unless, void, when)
import Control.Monad.IO.Class (liftIO)
Expand Down Expand Up @@ -53,19 +59,27 @@ import Test.Plutip.Config (
chainIndexMode,
clusterDataDir,
clusterWorkingDir,
extraConfig,
-- extraConfig,
relayNodeLogs
),
WorkingDirectory (Fixed, Temporary),
)
import Test.Plutip.Internal.BotPlutusInterface.Setup qualified as BotSetup
import Test.Plutip.Internal.Cluster (
ClusterLog,
RunningNode,
testMinSeverityFromEnv,
walletMinSeverityFromEnv,
withCluster,
)

-- import Test.Plutip.Internal.Cluster (
-- ClusterLog,
-- RunningNode,
-- testMinSeverityFromEnv,
-- walletMinSeverityFromEnv,
-- withCluster,
-- )
-- import Test.Plutip.Internal.Cluster (
-- ClusterLog,
-- RunningNode,
-- testMinSeverityFromEnv,
-- walletMinSeverityFromEnv,
-- withCluster,
-- )
import Test.Plutip.Internal.Types (
ClusterEnv (
ClusterEnv,
Expand All @@ -75,7 +89,7 @@ import Test.Plutip.Internal.Types (
runningNode,
supportDir,
tracer
),
), RunningNode
)
import Test.Plutip.Tools.CardanoApi qualified as Tools
import Text.Printf (printf)
Expand All @@ -84,7 +98,7 @@ import UnliftIO.Exception (bracket, catchIO, finally, throwString)
import UnliftIO.STM (TVar, atomically, newTVarIO, readTVar, retrySTM, writeTVar)

import Test.Plutip.Internal.ChainIndex (handleChainIndexLaunch)
import Test.Plutip.Internal.Cluster.Extra.Utils (localClusterConfigWithExtraConf)
-- import Test.Plutip.Internal.Cluster.Extra.Utils (localClusterConfigWithExtraConf)

-- | Starting a cluster with a setup action
-- We're heavily depending on cardano-wallet local cluster tooling, however they don't allow the
Expand Down Expand Up @@ -132,7 +146,8 @@ withPlutusInterface conf action = do
withLocalClusterSetup conf $ \dir clusterLogs _walletLogs nodeConfigLogHdl -> do
result <- withLoggingNamed "cluster" clusterLogs $ \(_, (_, trCluster)) -> do
let tr' = contramap MsgCluster $ trMessageText trCluster
clusterCfg <- localClusterConfigWithExtraConf (extraConfig conf)
-- clusterCfg <- localClusterConfigWithExtraConf (extraConfig conf)
clusterCfg <- localClusterConfigFromEnv
withRedirectedStdoutHdl nodeConfigLogHdl $ \restoreStdout ->
withCluster tr' dir clusterCfg mempty $ \rn -> do
restoreStdout $ runActionWthSetup rn dir trCluster action
Expand Down
5 changes: 3 additions & 2 deletions src/Test/Plutip/Internal/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Cardano.Api (NetworkId)
import Cardano.BM.Tracing (Trace)
import Cardano.Launcher.Node (CardanoNodeConn)

-- import Cardano.Wallet.Shelley.Launch.Cluster (RunningNode (RunningNode))
import Cardano.Wallet.Shelley.Launch.Cluster (RunningNode (RunningNode))

import Control.Exception (SomeException)
import Data.Either (isRight)
Expand All @@ -24,7 +24,8 @@ import Data.Text (Text)
import Ledger qualified
import Servant.Client (BaseUrl)
import Test.Plutip.Config (PlutipConfig)
import Test.Plutip.Internal.Cluster (RunningNode (RunningNode))

-- import Test.Plutip.Internal.Cluster (RunningNode (RunningNode))

-- | Environment for actions that use local cluster
data ClusterEnv = ClusterEnv
Expand Down
Loading

0 comments on commit 8e26b47

Please sign in to comment.