Skip to content

Commit bb708a4

Browse files
authored
Merge pull request #145 from mlabs-haskell/optional-chain-index
Optional launch of `chain-index`
2 parents 31ff4c4 + f8b7f89 commit bb708a4

File tree

13 files changed

+240
-105
lines changed

13 files changed

+240
-105
lines changed

CHANGELOG.md

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,24 @@ This format is based on [Keep A Changelog](https://keepachangelog.com/en/1.0.0).
77
- Wallets with Base Address support
88
- Lookups for wallets in tasty integration
99

10+
## [1.3.1] - 2022-10-26
11+
12+
### Added
13+
14+
- control on `chain-index` launch
15+
- `chainIndexPort` in `PlutipConfig` replaced with `chainIndexMode :: ChainIndexMode`
16+
- `local-cluster` options added: `--chain-index-port`, `--no-index`
17+
18+
## [1.2.1] - 2022-10-25
19+
20+
### Fixed
21+
22+
- eDSL function to await till wallet is funded `awaitWalletFunded`
23+
24+
### Added
25+
26+
- package with example of how to execute arbitrary contract on private network from Haskell
27+
1028
## [1.2.0] - 2022-10-21
1129

1230
### Added

README.md

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -41,19 +41,21 @@ NOTE: This branch launches local network in `Vasil`. It was tested with node `1.
4141
## Tutorials
4242

4343
* [Running disposable local network and building own runners](./local-cluster/README.md)
44+
* [Running chain-index](./docs/running-chain-index.md)
4445
* [Tasty integration](./docs/tasty-integration.md)
4546
* [Running Contracts is REPL](./docs/interactive-plutip.md)
4647
* [Providing constant keys](./docs/constant-keys.md)
4748

48-
## Examples
49-
50-
* [Starting private network from Haskell and executing contract](./contract-execution/Main.hs)
51-
5249
## Advanced network setup
5350

5451
* [Tweaking local network](./docs/tweaking-network.md)
5552
* [Regenerating network configs](./docs/regenerate-network-configs.md)
5653

54+
## Examples
55+
56+
* [Starting private network from Haskell and executing contract](./contract-execution/Main.hs)
57+
* [Template for setting a Nix flake that includes Plutip](https://github.com/MitchyCola/plutip-flake). Kudos to @MitchyCola
58+
5759
## Maintenance
5860

5961
* [Important notes on updating `cardano-wallet` dependency](./docs/cardano-wallet-update.md)

docs/running-chain-index.md

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
# Running chain index
2+
3+
It is possible to launch private network with or without `chain-index`.
4+
5+
This can be configured via `PlutipConfig` using `chainIndexMode :: ChainIndexMode` field. BE AWARE, that `chain-index` is required to run contracts with `Plutip` in [tasty integration](./tasty-integration.md), [interactive mode](./interactive-plutip.md) or with [custom runner](../contract-execution/Main.hs).
6+
7+
In case of `local-cluster` launch of `chain-index` can be controlled via options, see [readme](../local-cluster/README.md#available-arguments) for details.

local-cluster/Main.hs

Lines changed: 27 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
module Main (main) where
77

88
import Cardano.Ledger.Slot (EpochSize (EpochSize))
9-
import Control.Applicative (optional, (<**>))
9+
import Control.Applicative (optional, (<**>), (<|>))
1010
import Control.Monad (forM_, replicateM, void)
1111
import Control.Monad.IO.Class (liftIO)
1212
import Control.Monad.Reader (ReaderT (ReaderT))
@@ -18,7 +18,8 @@ import Numeric.Positive (Positive)
1818
import Options.Applicative (Parser, helper, info)
1919
import Options.Applicative qualified as Options
2020
import Test.Plutip.Config (
21-
PlutipConfig (clusterWorkingDir, extraConfig),
21+
ChainIndexMode (CustomPort, DefaultPort, NotNeeded),
22+
PlutipConfig (chainIndexMode, clusterWorkingDir, extraConfig),
2223
WorkingDirectory (Fixed, Temporary),
2324
)
2425
import Test.Plutip.Internal.BotPlutusInterface.Wallet (
@@ -43,11 +44,11 @@ main = do
4344
case totalAmount config of
4445
Left e -> error e
4546
Right amt -> do
46-
let ClusterConfig {numWallets, dirWallets, numUtxos, workDir, slotLength, epochSize} = config
47+
let ClusterConfig {numWallets, dirWallets, numUtxos, workDir, slotLength, epochSize, cIndexMode} = config
4748
workingDir = maybe Temporary (`Fixed` False) workDir
4849

4950
extraConf = ExtraConfig slotLength epochSize
50-
plutipConfig = def {clusterWorkingDir = workingDir, extraConfig = extraConf}
51+
plutipConfig = def {clusterWorkingDir = workingDir, extraConfig = extraConf, chainIndexMode = cIndexMode}
5152

5253
putStrLn "Starting cluster..."
5354
(st, _) <- startCluster plutipConfig $ do
@@ -177,6 +178,26 @@ pEpochSize =
177178
<> Options.value 160
178179
)
179180

181+
pChainIndexMode :: Parser ChainIndexMode
182+
pChainIndexMode =
183+
noIndex <|> withIndexPort <|> pure DefaultPort
184+
where
185+
noIndex =
186+
Options.flag'
187+
NotNeeded
188+
( Options.long "no-index"
189+
<> Options.help "Start cluster with chain-index on default port"
190+
)
191+
withIndexPort = CustomPort <$> portParser
192+
193+
portParser =
194+
Options.option
195+
Options.auto
196+
( Options.long "chain-index-port"
197+
<> Options.metavar "PORT"
198+
<> Options.help "Start cluster with chain-index on custom port"
199+
)
200+
180201
pClusterConfig :: Parser ClusterConfig
181202
pClusterConfig =
182203
ClusterConfig
@@ -188,6 +209,7 @@ pClusterConfig =
188209
<*> pWorkDir
189210
<*> pSlotLen
190211
<*> pEpochSize
212+
<*> pChainIndexMode
191213

192214
-- | Basic info about the cluster, to
193215
-- be used by the command-line
@@ -200,5 +222,6 @@ data ClusterConfig = ClusterConfig
200222
, workDir :: Maybe FilePath
201223
, slotLength :: NominalDiffTime
202224
, epochSize :: EpochSize
225+
, cIndexMode :: ChainIndexMode
203226
}
204227
deriving stock (Show, Eq)

local-cluster/README.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,8 @@ Full | Short | Description
4040
--working-dir /path/ | -w /path/ | This determines where the node database, chain-index database, and bot-plutus-interface files will be stored for a running cluster. If specified, this will store cluster data in the provided path (can be relative or absolute), the files will be deleted on cluster shutdown by default. Otherwise, the cluster data is stored in a temporary directory and will be deleted on cluster shutdown.
4141
--slot-len SECONDS | -s SECONDS | Sets slot length of created network, is seconds. E.g. `--slot-len 1s`, `-s 0.2s`. <br /> Addition of `s` is important for correct parsing of this option.
4242
--epoch-size NUM | -s NUM | Sets epoch size of created network, is slots.
43+
--slot-len SECONDS | -s SECONDS | Sets slot length of created network, is seconds. E.g. `--slot-len 1s`, `-s 0.2s`. <br /> Addition of `s` is important for correct parsing of this option.
44+
--chain-index-port PORT<br />or<br />--no-index| - | With `--chain-index-port` and `PORT` specified `chain-index` will be launched on specified port together with private network.<br /> With `--no-index` only private network will be launched without `chain-index`.<br /> When nothing specified `chain-index` will be launched on default port `9083`.<br />
4345

4446
## Making own local network launcher
4547

plutip-server/Api/Handlers.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,8 +21,9 @@ import Data.Traversable (for)
2121
import System.Directory (doesFileExist)
2222
import System.FilePath (replaceFileName)
2323
import Test.Plutip.Config (
24+
ChainIndexMode (NotNeeded),
2425
PlutipConfig (extraConfig),
25-
chainIndexPort,
26+
chainIndexMode,
2627
relayNodeLogs,
2728
)
2829
import Test.Plutip.Internal.BotPlutusInterface.Setup (keysDir)
@@ -80,7 +81,7 @@ startClusterHandler
8081
isClusterDown <- liftIO $ isEmptyMVar statusMVar
8182
unless isClusterDown $ throwError ClusterIsRunningAlready
8283
let extraConf = ExtraConfig slotLength epochSize
83-
cfg = def {relayNodeLogs = nodeLogs, chainIndexPort = Nothing, extraConfig = extraConf}
84+
cfg = def {relayNodeLogs = nodeLogs, chainIndexMode = NotNeeded, extraConfig = extraConf}
8485

8586
(statusTVar, res@(clusterEnv, _)) <- liftIO $ startCluster cfg setup
8687
liftIO $ putMVar statusMVar statusTVar

plutip.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -161,6 +161,7 @@ library
161161
Test.Plutip.Internal.BotPlutusInterface.Setup
162162
Test.Plutip.Internal.BotPlutusInterface.Types
163163
Test.Plutip.Internal.BotPlutusInterface.Wallet
164+
Test.Plutip.Internal.ChainIndex
164165
Test.Plutip.Internal.Cluster
165166
Test.Plutip.Internal.Cluster.Extra.Types
166167
Test.Plutip.Internal.Cluster.Extra.Utils

src/Test/Plutip/Config.hs

Lines changed: 16 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module Test.Plutip.Config (
22
PlutipConfig (..),
33
WorkingDirectory (..),
4+
ChainIndexMode (..),
45
) where
56

67
import Cardano.Api (PaymentKey, SigningKey)
@@ -35,8 +36,9 @@ data PlutipConfig = PlutipConfig
3536
clusterDataDir :: Maybe FilePath
3637
, -- | in case of `Just path` relay node log will be saved to specified file
3738
relayNodeLogs :: Maybe FilePath
38-
, -- | in case of `Nothing` port from `Plutus.ChainIndex.Config.defaultConfig` is used
39-
chainIndexPort :: Maybe Natural
39+
, -- | the way of how `chain-index` is launched (default port, custom port, not launched),
40+
-- default mode - default port
41+
chainIndexMode :: ChainIndexMode
4042
, -- | Multiplier on all BPI transaction budgets
4143
budgetMultiplier :: Rational
4244
, -- | cluster file location override, when provided, includes a `shouldKeep`
@@ -50,5 +52,16 @@ data PlutipConfig = PlutipConfig
5052
}
5153
deriving stock (Generic, Show)
5254

55+
-- | The way to launch `chain-index`.
56+
-- It is possible to not launch it at all.
57+
data ChainIndexMode
58+
= -- | launch on default port `9083`
59+
DefaultPort
60+
| -- | launch on custom port
61+
CustomPort Natural
62+
| -- | do not launch at all
63+
NotNeeded
64+
deriving stock (Generic, Eq, Show)
65+
5366
instance Default PlutipConfig where
54-
def = PlutipConfig Nothing Nothing Nothing 1 Temporary [] def
67+
def = PlutipConfig Nothing Nothing DefaultPort 1 Temporary [] def

src/Test/Plutip/Internal/BotPlutusInterface/Run.hs

Lines changed: 21 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -108,23 +108,34 @@ runContractWithLogLvl logLvl cEnv bpiWallet contract = do
108108
fromRight (error "Could not read protocol parameters file.")
109109
<$> liftIO (eitherDecodeFileStrict' (BIS.pParamsFile cEnv))
110110

111-
contactEnv <- liftIO $ mkEnv (mkPabConfig pparams)
111+
chIndexUrl <-
112+
maybe
113+
( error
114+
"To run the contract with Plutip Chain Index must be launched, \
115+
\ but it seems to be off.\
116+
\ Check `ChainIndexMode` in `PlutipConfig`"
117+
)
118+
pure
119+
(chainIndexUrl cEnv)
120+
121+
contactEnv <- mkEnv (mkPabConfig pparams chIndexUrl)
112122

113123
runContract' contactEnv
114124
where
115125
mkEnv pabConf =
116-
ContractEnvironment pabConf
117-
<$> ContractInstanceId
118-
<$> UUID.nextRandom
119-
<*> newTVarIO (ContractState Active (mempty :: w))
120-
<*> newTVarIO mempty
121-
<*> newTVarIO mempty
122-
<*> (Bpi.CollateralVar <$> newTVarIO Nothing)
126+
liftIO $
127+
ContractEnvironment pabConf
128+
<$> ContractInstanceId
129+
<$> UUID.nextRandom
130+
<*> newTVarIO (ContractState Active (mempty :: w))
131+
<*> newTVarIO mempty
132+
<*> newTVarIO mempty
133+
<*> (Bpi.CollateralVar <$> newTVarIO Nothing)
123134

124-
mkPabConfig pparams =
135+
mkPabConfig pparams chIndexUrl =
125136
PABConfig
126137
{ pcCliLocation = Local
127-
, pcChainIndexUrl = chainIndexUrl cEnv
138+
, pcChainIndexUrl = chIndexUrl
128139
, pcNetwork = networkId cEnv
129140
, pcProtocolParams = pparams
130141
, pcScriptFileDir = Text.pack $ BIS.scriptsDir cEnv
Lines changed: 103 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,103 @@
1+
module Test.Plutip.Internal.ChainIndex (
2+
handleChainIndexLaunch,
3+
) where
4+
5+
import Cardano.Api qualified as CAPI
6+
import Cardano.BM.Configuration.Model qualified as CM
7+
import Cardano.BM.Data.Severity qualified as Severity
8+
import Cardano.Launcher.Node (nodeSocketFile)
9+
10+
import Control.Concurrent.Async (async)
11+
import Control.Monad (void)
12+
import Control.Retry (constantDelay, limitRetries, recoverAll)
13+
import Plutus.ChainIndex.App qualified as ChainIndex
14+
import Plutus.ChainIndex.Config qualified as ChainIndex
15+
import Plutus.ChainIndex.Logging (defaultConfig)
16+
import Servant.Client (BaseUrl (BaseUrl), Scheme (Http), mkClientEnv, runClientM)
17+
import System.FilePath ((</>))
18+
import Test.Plutip.Config (
19+
ChainIndexMode (CustomPort, DefaultPort, NotNeeded),
20+
)
21+
import Test.Plutip.Internal.Types (
22+
RunningNode (RunningNode),
23+
)
24+
import UnliftIO.Exception (throwString)
25+
26+
import Cardano.Wallet.Primitive.Types (
27+
NetworkParameters (NetworkParameters),
28+
SlotLength (SlotLength),
29+
SlottingParameters (SlottingParameters),
30+
)
31+
import Data.Default (Default (def))
32+
import Data.Function ((&))
33+
import Data.Time (nominalDiffTimeToSeconds)
34+
import Ledger (Slot (Slot))
35+
import Ledger.TimeSlot (SlotConfig (scSlotLength))
36+
import Network.HTTP.Client (defaultManagerSettings, newManager)
37+
import Plutus.ChainIndex (Tip (Tip))
38+
import Plutus.ChainIndex.Client qualified as ChainIndexClient
39+
import Plutus.ChainIndex.Config qualified as CIC
40+
import PlutusPrelude ((.~), (^.))
41+
42+
type ChainIndexPort = Int
43+
44+
-- | Handle launch of `chain-index`. Depending on `ChainIndexMode`, it can be
45+
-- launched on default port, on custom port or not launched at all.
46+
-- In the latter case no port will be returned.
47+
handleChainIndexLaunch ::
48+
ChainIndexMode ->
49+
RunningNode ->
50+
FilePath ->
51+
IO (Maybe ChainIndexPort)
52+
handleChainIndexLaunch mode rn dir = do
53+
maybePort <-
54+
case mode of
55+
DefaultPort -> do
56+
Just <$> launchChainIndex (CIC.cicPort ChainIndex.defaultConfig) rn dir
57+
CustomPort port' -> do
58+
Just <$> launchChainIndex (fromEnum port') rn dir
59+
NotNeeded -> pure Nothing
60+
reportLaunch maybePort
61+
pure maybePort
62+
where
63+
reportLaunch = \case
64+
Just p -> putStrLn $ "Chain index started at port " <> show p
65+
_ -> pure ()
66+
67+
-- | Launch the chain index in a separate thread.
68+
launchChainIndex :: Int -> RunningNode -> FilePath -> IO Int
69+
launchChainIndex port (RunningNode sp _block0 (netParams, _vData) _) dir = do
70+
let (NetworkParameters _ (SlottingParameters (SlotLength slotLen) _ _ _) _) = netParams
71+
72+
config <- defaultConfig
73+
CM.setMinSeverity config Severity.Notice
74+
let dbPath = dir </> "chain-index.db"
75+
chainIndexConfig =
76+
CIC.defaultConfig
77+
& CIC.socketPath .~ nodeSocketFile sp
78+
& CIC.dbPath .~ dbPath
79+
& CIC.networkId .~ CAPI.Mainnet
80+
& CIC.port .~ port
81+
& CIC.slotConfig .~ (def {scSlotLength = toMilliseconds slotLen})
82+
83+
void $ async $ void $ ChainIndex.runMainWithLog (const $ return ()) config chainIndexConfig
84+
waitForChainIndex
85+
return $ chainIndexConfig ^. CIC.port
86+
where
87+
toMilliseconds = floor . (1e3 *) . nominalDiffTimeToSeconds
88+
89+
waitForChainIndex = do
90+
-- TODO: move this to config; ideally, separate chain-index launch from cluster launch
91+
let policy = constantDelay 1_000_000 <> limitRetries 60
92+
recoverAll policy $ \_ -> do
93+
tip <- queryTipWithChIndex
94+
case tip of
95+
Right (Tip (Slot _) _ _) -> pure ()
96+
a ->
97+
throwString $
98+
"Timeout waiting for chain-index to start indexing. Last response:\n"
99+
<> either show show a
100+
101+
queryTipWithChIndex = do
102+
manager' <- newManager defaultManagerSettings
103+
runClientM ChainIndexClient.getTip $ mkClientEnv manager' (BaseUrl Http "localhost" port "")

0 commit comments

Comments
 (0)