@@ -39,7 +39,7 @@ import Paths_plutip (getDataFileName)
3939import Plutus.ChainIndex.App qualified as ChainIndex
4040import Plutus.ChainIndex.Config qualified as ChainIndex
4141import Plutus.ChainIndex.Logging (defaultConfig )
42- import Servant.Client (BaseUrl (BaseUrl ), Scheme (Http ))
42+ import Servant.Client (BaseUrl (BaseUrl ), Scheme (Http ), mkClientEnv , runClientM )
4343import System.Directory (canonicalizePath , copyFile , createDirectoryIfMissing , doesPathExist , findExecutable , removeDirectoryRecursive )
4444import System.Environment (setEnv )
4545import System.Exit (die )
@@ -70,7 +70,7 @@ import Test.Plutip.Internal.Types (
7070import Test.Plutip.Tools.CardanoApi qualified as Tools
7171import Text.Printf (printf )
7272import UnliftIO.Concurrent (forkFinally , myThreadId , throwTo )
73- import UnliftIO.Exception (bracket , catchIO , finally )
73+ import UnliftIO.Exception (bracket , catchIO , finally , throwString )
7474import UnliftIO.STM (TVar , atomically , newTVarIO , readTVar , retrySTM , writeTVar )
7575
7676import Cardano.Wallet.Primitive.Types (
@@ -81,7 +81,11 @@ import Cardano.Wallet.Primitive.Types (
8181import Data.Default (Default (def ))
8282import Data.Function ((&) )
8383import Data.Time (nominalDiffTimeToSeconds )
84+ import Ledger (Slot (Slot ))
8485import Ledger.TimeSlot (SlotConfig (scSlotLength ))
86+ import Network.HTTP.Client (defaultManagerSettings , newManager )
87+ import Plutus.ChainIndex (Tip (Tip ))
88+ import Plutus.ChainIndex.Client qualified as ChainIndexClient
8589import Plutus.ChainIndex.Config qualified as CIC
8690import PlutusPrelude ((.~) , (^.) )
8791
@@ -145,7 +149,7 @@ withPlutusInterface conf action = do
145149 runActionWthSetup rn dir trCluster userActon = do
146150 let tracer' = trMessageText trCluster
147151 waitForRelayNode tracer' rn
148- -- launch chain index in seperate thread, logs to stdout
152+ -- launch chain index in separate thread
149153 ciPort <- launchChainIndex conf rn dir
150154 traceWith tracer' (ChaiIndexStartedAt ciPort)
151155 let cEnv =
@@ -250,8 +254,10 @@ waitForRelayNode trCluster rn =
250254 getTip = trace >> Tools. queryTip rn
251255 trace = traceWith trCluster WaitingRelayNode
252256 wait _ = do
253- -- give some time for setup
254- (ChainTip (SlotNo ((> 5 ) -> True )) _ _) <- getTip
257+ tip <- getTip
258+ case tip of
259+ (ChainTip (SlotNo _) _ _) -> pure ()
260+ _ -> throwString " Timeout waiting for node to start"
255261 pure ()
256262
257263-- | Launch the chain index in a separate thread.
@@ -262,19 +268,33 @@ launchChainIndex conf (RunningNode sp _block0 (netParams, _vData) _) dir = do
262268 config <- defaultConfig
263269 CM. setMinSeverity config Severity. Notice
264270 let dbPath = dir </> " chain-index.db"
271+ port = maybe (CIC. cicPort ChainIndex. defaultConfig) fromEnum (chainIndexPort conf)
265272 chainIndexConfig =
266273 CIC. defaultConfig
267- & CIC. socketPath .~ nodeSocketFile sp
274+ & CIC. socketPath .~ ( nodeSocketFile sp ++ " lol " )
268275 & CIC. dbPath .~ dbPath
269276 & CIC. networkId .~ CAPI. Mainnet
270277 & CIC. port .~ maybe (CIC. cicPort ChainIndex. defaultConfig) fromEnum (chainIndexPort conf)
271278 & CIC. slotConfig .~ (def {scSlotLength = toMilliseconds slotLen})
272279
273280 void . async $ void $ ChainIndex. runMainWithLog (const $ return () ) config chainIndexConfig
281+ waitForChainIndex port
274282 return $ chainIndexConfig ^. CIC. port
275283 where
276284 toMilliseconds = floor . (1e3 * ) . nominalDiffTimeToSeconds
277285
286+ waitForChainIndex port = do
287+ let policy = constantDelay 500000 <> limitRetries 50
288+ recoverAll policy $ \ _ -> do
289+ tip <- queryTipWithChIndex port
290+ case tip of
291+ Right (Tip (Slot _) _ _) -> pure ()
292+ _ -> throwString " Timeout waiting for chain-index to start"
293+
294+ queryTipWithChIndex port = do
295+ manager' <- newManager defaultManagerSettings
296+ runClientM ChainIndexClient. getTip $ mkClientEnv manager' (BaseUrl Http " localhost" port " " )
297+
278298handleLogs :: HasCallStack => FilePath -> PlutipConfig -> IO ()
279299handleLogs clusterDir conf =
280300 copyRelayLog `catchIO` (error . printf " Failed to save relay node log: %s" . show )
0 commit comments