66{-# LANGUAGE OverloadedStrings #-}
77{-# LANGUAGE ScopedTypeVariables #-}
88{-# LANGUAGE TupleSections #-}
9+ {-# LANGUAGE TypeApplications #-}
910{-# LANGUAGE TypeFamilies #-}
1011{-# LANGUAGE TypeOperators #-}
12+ {-# LANGUAGE RankNTypes #-}
1113
1214module Testnet.Start.Cardano
1315 ( CardanoTestnetCliOptions (.. )
@@ -32,17 +34,18 @@ import Cardano.Api
3234import Cardano.Api.Byron (GenesisData (.. ))
3335import qualified Cardano.Api.Byron as Byron
3436
35- import Cardano.Node.Configuration.Topology (RemoteAddress (.. ))
37+ import Cardano.Node.Configuration.Topology (RemoteAddress (.. ))
3638import qualified Cardano.Node.Configuration.Topology as Direct
3739import qualified Cardano.Node.Configuration.TopologyP2P as P2P
3840import Cardano.Prelude (canonicalEncodePretty )
39- import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint (.. ))
41+ import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint (.. ))
4042
4143import Prelude hiding (lines )
4244
4345import Control.Concurrent (threadDelay )
44- import Control.Monad
46+ import Control.Monad
4547import Control.Monad.Catch
48+ import Control.Monad.Trans.Resource (MonadResource , getInternalState )
4649import Data.Aeson
4750import qualified Data.Aeson.Encode.Pretty as A
4851import qualified Data.Aeson.KeyMap as A
@@ -64,6 +67,7 @@ import Testnet.Components.Configuration
6467import qualified Testnet.Defaults as Defaults
6568import Testnet.Filepath
6669import Testnet.Handlers (interruptNodesOnSigINT )
70+ import Testnet.Orphans ()
6771import Testnet.Process.RunIO (execCli' , execCli_ , liftIOAnnotated , mkExecConfig )
6872import Testnet.Property.Assert (assertChainExtended , assertExpectedSposInLedgerState )
6973import Testnet.Runtime as TR
@@ -72,13 +76,11 @@ import Testnet.Types as TR hiding (shelleyGenesis)
7276
7377import qualified Hedgehog.Extras as H
7478import qualified Hedgehog.Extras.Stock.IO.Network.Port as H
79+ import Hedgehog.Internal.Property (failException )
7580
76-
77- import RIO (RIO (.. ),runRIO , throwString , MonadUnliftIO )
78- import Control.Monad.Trans.Resource (getInternalState , MonadResource )
79- import Testnet.Orphans ()
80- import RIO.Orphans (ResourceMap )
81- import UnliftIO.Async
81+ import RIO (MonadUnliftIO , RIO (.. ), runRIO , stringException , throwString )
82+ import RIO.Orphans (ResourceMap )
83+ import UnliftIO.Async
8284
8385
8486-- | There are certain conditions that need to be met in order to run
@@ -91,10 +93,10 @@ testMinimumConfigurationRequirements options = withFrozenCallStack $ do
9193 when (cardanoNumPools options < 1 ) $ do
9294 throwString " Need at least one SPO node to produce blocks, but got none."
9395
94- liftToIntegration :: HasCallStack => RIO ResourceMap a -> H. Integration a
95- liftToIntegration r = do
96- rMap <- lift $ lift getInternalState
97- liftIOAnnotated $ runRIO rMap r
96+ liftToIntegration :: HasCallStack => RIO ResourceMap a -> H. Integration a
97+ liftToIntegration r = do
98+ rMap <- lift $ lift getInternalState
99+ catch @ _ @ SomeException ( runRIO rMap r) (withFrozenCallStack $ failException . toException . stringException . displayException)
98100
99101createTestnetEnv :: ()
100102 => HasCallStack
@@ -222,7 +224,7 @@ createTestnetEnv
222224-- > ├── configuration.json
223225-- > ├── current-stake-pools.json
224226-- > └── module
225- cardanoTestnet
227+ cardanoTestnet
226228 :: HasCallStack
227229 => MonadUnliftIO m
228230 => MonadResource m
@@ -248,8 +250,8 @@ cardanoTestnet
248250 shelleyGenesisFile = tmpAbsPath </> " shelley-genesis.json"
249251
250252 sBytes <- liftIOAnnotated (LBS. readFile shelleyGenesisFile)
251- shelleyGenesis@ ShelleyGenesis {sgNetworkMagic}
252- <- case eitherDecode sBytes of
253+ shelleyGenesis@ ShelleyGenesis {sgNetworkMagic}
254+ <- case eitherDecode sBytes of
253255 Right sg -> return sg
254256 Left err -> throwString $ " Could not decode shelley genesis file: " <> shelleyGenesisFile <> " Error: " <> err
255257 let testnetMagic :: Int = fromIntegral sgNetworkMagic
@@ -337,8 +339,8 @@ cardanoTestnet
337339
338340 -- Update start time in Byron genesis file
339341 eByron <- runExceptT $ Byron. readGenesisData byronGenesisFile
340- (byronGenesis', _byronHash) <-
341- case eByron of
342+ (byronGenesis', _byronHash) <-
343+ case eByron of
342344 Right bg -> return bg
343345 Left err -> throwString $ " Could not read byron genesis data from file: " <> byronGenesisFile <> " Error: " <> show err
344346 let byronGenesis = byronGenesis'{gdStartTime = startTime}
0 commit comments