Skip to content

Commit dbe4123

Browse files
authored
Merge pull request #6010 from IntersectMBO/mgalazyn/chore/remove-redundant-functions
cardano-testnet | Remove redundant functions used for starting a process
2 parents ca38b9d + dcf448b commit dbe4123

File tree

5 files changed

+20
-194
lines changed

5 files changed

+20
-194
lines changed

cardano-testnet/cardano-testnet.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,6 @@ library
8585
, tasty-expected-failure
8686
, tasty-hedgehog
8787
, template-haskell
88-
, temporary
8988
, text
9089
, time
9190
, transformers

cardano-testnet/src/Testnet/Process/Run.hs

Lines changed: 4 additions & 130 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ module Testnet.Process.Run
1717
, mkExecConfig
1818
, mkExecConfigOffline
1919
, ProcessError(..)
20-
, ExecutableError(..)
2120
, addEnvVarsToConfig
2221
) where
2322

@@ -31,29 +30,21 @@ import Control.Monad.Trans.Except (ExceptT)
3130
import Control.Monad.Trans.Except.Extra
3231
import Control.Monad.Trans.Resource
3332
import qualified Data.Aeson as Aeson
34-
import qualified Data.ByteString.Lazy as LBS
35-
import Data.Function
36-
import qualified Data.List as List
37-
import Data.Maybe (fromMaybe)
33+
import Data.Maybe
3834
import Data.Monoid (Last (..))
3935
import Data.String (fromString)
40-
import qualified Data.Text as Text
4136
import GHC.Stack (HasCallStack)
4237
import qualified GHC.Stack as GHC
43-
import qualified System.Directory as IO
4438
import qualified System.Environment as IO
4539
import System.Exit (ExitCode)
46-
import System.FilePath
4740
import System.IO
4841
import qualified System.IO.Unsafe as IO
4942
import qualified System.Process as IO
5043
import System.Process
5144

5245
import Hedgehog (MonadTest)
5346
import qualified Hedgehog.Extras as H
54-
import Hedgehog.Extras.Internal.Plan (Component (..), Plan (..))
5547
import qualified Hedgehog.Extras.Stock.IO.Network.Sprocket as IO
56-
import qualified Hedgehog.Extras.Stock.OS as OS
5748
import Hedgehog.Extras.Test.Process (ExecConfig)
5849
import qualified Hedgehog.Internal.Property as H
5950

@@ -146,13 +137,12 @@ procCli = GHC.withFrozenCallStack $ H.procFlex "cardano-cli" "CARDANO_CLI"
146137
-- | Create a 'CreateProcess' describing how to start the cardano-node process
147138
-- and an argument list.
148139
procNode
149-
:: HasCallStack
150-
=> MonadIO m
140+
:: (MonadTest m, MonadCatch m, MonadIO m, HasCallStack)
151141
=> [String]
152142
-- ^ Arguments to the CLI command
153-
-> ExceptT ExecutableError m CreateProcess
143+
-> m CreateProcess
154144
-- ^ Captured stdout
155-
procNode = GHC.withFrozenCallStack $ procFlexNew "cardano-node" "CARDANO_NODE"
145+
procNode = GHC.withFrozenCallStack $ H.procFlex "cardano-node" "CARDANO_NODE"
156146

157147
-- | Create a 'CreateProcess' describing how to start the cardano-submit-api process
158148
-- and an argument list.
@@ -248,119 +238,3 @@ resourceAndIOExceptionHandlers = [ Handler $ pure . ProcessIOException
248238
, Handler $ pure . ResourceException
249239
]
250240

251-
procFlexNew
252-
:: MonadIO m
253-
=> String
254-
-- ^ Cabal package name corresponding to the executable
255-
-> String
256-
-- ^ Environment variable pointing to the binary to run
257-
-> [String]
258-
-- ^ Arguments to the CLI command
259-
-> ExceptT ExecutableError m CreateProcess
260-
-- ^ Captured stdout
261-
procFlexNew = procFlexNew' H.defaultExecConfig
262-
263-
procFlexNew'
264-
:: MonadIO m
265-
=> H.ExecConfig
266-
-> String
267-
-- ^ Cabal package name corresponding to the executable
268-
-> String
269-
-- ^ Environment variable pointing to the binary to run
270-
-> [String]
271-
-- ^ Arguments to the CLI command
272-
-> ExceptT ExecutableError m CreateProcess
273-
-- ^ Captured stdout
274-
procFlexNew' execConfig pkg binaryEnv arguments = GHC.withFrozenCallStack $ do
275-
bin <- binFlexNew pkg binaryEnv
276-
pure (IO.proc bin arguments)
277-
{ IO.env = getLast $ H.execConfigEnv execConfig
278-
, IO.cwd = getLast $ H.execConfigCwd execConfig
279-
-- this allows sending signals to the created processes, without killing the test-suite process
280-
, IO.create_group = True
281-
}
282-
283-
-- | Compute the path to the binary given a package name or an environment variable override.
284-
binFlexNew
285-
:: MonadIO m
286-
=> String
287-
-- ^ Package name
288-
-> String
289-
-- ^ Environment variable pointing to the binary to run
290-
-> ExceptT ExecutableError m FilePath
291-
-- ^ Path to executable
292-
binFlexNew pkg binaryEnv = do
293-
maybeEnvBin <- liftIO $ IO.lookupEnv binaryEnv
294-
case maybeEnvBin of
295-
Just envBin -> return envBin
296-
Nothing -> binDist pkg
297-
298-
-- | Find the nearest plan.json going upwards from the current directory.
299-
findDefaultPlanJsonFile :: IO FilePath
300-
findDefaultPlanJsonFile = IO.getCurrentDirectory >>= go
301-
where go :: FilePath -> IO FilePath
302-
go d = do
303-
let file = d </> "dist-newstyle/cache/plan.json"
304-
exists <- IO.doesFileExist file
305-
if exists
306-
then return file
307-
else do
308-
let parent = takeDirectory d
309-
if parent == d
310-
then return "dist-newstyle/cache/plan.json"
311-
else go parent
312-
313-
314-
-- | Discover the location of the plan.json file.
315-
planJsonFile :: IO FilePath
316-
planJsonFile = do
317-
maybeBuildDir <- liftIO $ IO.lookupEnv "CABAL_BUILDDIR"
318-
case maybeBuildDir of
319-
Just buildDir -> return $ ".." </> buildDir </> "cache/plan.json"
320-
Nothing -> findDefaultPlanJsonFile
321-
{-# NOINLINE planJsonFile #-}
322-
323-
data ExecutableError
324-
= CannotDecodePlanJSON FilePath String
325-
| RetrievePlanJsonFailure IOException
326-
| ReadFileFailure IOException
327-
| ExecutableMissingInComponent FilePath String
328-
-- ^ Component with key @component-name@ is found, but it is missing
329-
-- the @bin-file@ key.
330-
| ExecutableNotFoundInPlan String
331-
-- ^ Component with key @component-name@ cannot be found
332-
deriving Show
333-
334-
335-
-- | Consult the "plan.json" generated by cabal to get the path to the executable corresponding.
336-
-- to a haskell package. It is assumed that the project has already been configured and the
337-
-- executable has been built.
338-
binDist
339-
:: MonadIO m
340-
=> String
341-
-- ^ Package name
342-
-> ExceptT ExecutableError m FilePath
343-
-- ^ Path to executable
344-
binDist pkg = do
345-
pJsonFp <- handleIOExceptT RetrievePlanJsonFailure planJsonFile
346-
contents <- handleIOExceptT ReadFileFailure $ LBS.readFile pJsonFp
347-
348-
case Aeson.eitherDecode contents of
349-
Right plan -> case List.filter matching (plan & installPlan) of
350-
(component:_) -> case component & binFile of
351-
Just bin -> return $ addExeSuffix (Text.unpack bin)
352-
Nothing -> left $ ExecutableMissingInComponent pJsonFp $ "missing \"bin-file\" key in plan component: " <> show component
353-
[] -> left $ ExecutableNotFoundInPlan $ "Cannot find \"component-name\" key with value \"exe:" <> pkg <> "\""
354-
Left message -> left $ CannotDecodePlanJSON pJsonFp $ "Cannot decode plan: " <> message
355-
where matching :: Component -> Bool
356-
matching component = case componentName component of
357-
Just name -> name == Text.pack ("exe:" <> pkg)
358-
Nothing -> False
359-
360-
addExeSuffix :: String -> String
361-
addExeSuffix s = if ".exe" `List.isSuffixOf` s
362-
then s
363-
else s <> exeSuffix
364-
365-
exeSuffix :: String
366-
exeSuffix = if OS.isWin32 then ".exe" else ""

cardano-testnet/src/Testnet/Property/Util.hs

Lines changed: 3 additions & 49 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE FlexibleContexts #-}
33
{-# LANGUAGE MonoLocalBinds #-}
4-
{-# LANGUAGE NumericUnderscores #-}
54
{-# LANGUAGE OverloadedStrings #-}
65
{-# LANGUAGE ScopedTypeVariables #-}
76

@@ -16,23 +15,14 @@ module Testnet.Property.Util
1615

1716
import Cardano.Api
1817

19-
import Control.Exception.Safe
20-
import Control.Monad
21-
import Control.Monad.Trans.Resource
22-
import qualified Control.Retry as R
2318
import qualified Data.Aeson as Aeson
2419
import GHC.Stack
25-
import qualified System.Directory as IO
2620
import qualified System.Environment as IO
27-
import System.FilePath ((</>))
2821
import System.Info (os)
29-
import qualified System.IO as IO
30-
import qualified System.IO.Temp as IO
3122
import qualified System.IO.Unsafe as IO
3223

3324
import qualified Hedgehog as H
3425
import qualified Hedgehog.Extras as H
35-
import qualified Hedgehog.Extras.Stock.CallStack as H
3626
import Hedgehog.Internal.Property (MonadTest)
3727

3828

@@ -53,52 +43,16 @@ integrationRetryWorkspace n workspaceName f = withFrozenCallStack $
5343
if disableRetries
5444
then
5545
integration $
56-
H.runFinallies $ workspace (workspaceName <> "-no-retries") f
46+
H.runFinallies $ H.workspace (workspaceName <> "-no-retries") f
5747
else
5848
integration $ H.retry n $ \i ->
59-
H.runFinallies $ workspace (workspaceName <> "-" <> show i) f
60-
61-
-- | Create a workspace directory which will exist for at least the duration of
62-
-- the supplied block.
63-
--
64-
-- The directory will have the supplied prefix but contain a generated random
65-
-- suffix to prevent interference between tests
66-
--
67-
-- The directory will be deleted if the block succeeds, but left behind if
68-
-- the block fails.
69-
-- TODO: this is a version which retries deleting of a workspace on exception - upstream to hedgehog-extras
70-
workspace
71-
:: MonadTest m
72-
=> HasCallStack
73-
=> MonadResource m
74-
=> FilePath
75-
-> (FilePath -> m ())
76-
-> m ()
77-
workspace prefixPath f = withFrozenCallStack $ do
78-
systemTemp <- H.evalIO IO.getCanonicalTemporaryDirectory
79-
maybeKeepWorkspace <- H.evalIO $ IO.lookupEnv "KEEP_WORKSPACE"
80-
ws <- H.evalIO $ IO.createTempDirectory systemTemp $ prefixPath <> "-test"
81-
H.annotate $ "Workspace: " <> ws
82-
H.evalIO $ IO.writeFile (ws </> "module") H.callerModuleName
83-
f ws
84-
when (os /= "mingw32" && maybeKeepWorkspace /= Just "1") $ do
85-
-- try to delete the directory 5 times, 100ms apart
86-
let retryPolicy = R.constantDelay 100_000 <> R.limitRetries 10
87-
-- retry only on IOExceptions
88-
ioExH _ = Handler $ \(_ :: IOException) -> pure True
89-
-- For some reason, the temporary directory removal sometimes fails.
90-
-- Lets wrap this in MonadResource try multiple times before we fail.
91-
void
92-
. register
93-
. R.recovering retryPolicy [ioExH]
94-
. const
95-
$ IO.removePathForcibly ws
49+
H.runFinallies $ H.workspace (workspaceName <> "-" <> show i) f
9650

9751
-- | The 'FilePath' in '(FilePath -> H.Integration ())' is the work space directory.
9852
-- This is created (and returned) via 'H.workspace'.
9953
integrationWorkspace :: HasCallStack => FilePath -> (FilePath -> H.Integration ()) -> H.Property
10054
integrationWorkspace workspaceName f = withFrozenCallStack $
101-
integration $ H.runFinallies $ workspace workspaceName f
55+
integration $ H.runFinallies $ H.workspace workspaceName f
10256

10357
isLinux :: Bool
10458
isLinux = os == "linux"

cardano-testnet/src/Testnet/Runtime.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ import qualified Hedgehog.Extras.Test.Concurrent as H
6060

6161
data NodeStartFailure
6262
= ProcessRelatedFailure ProcessError
63-
| ExecutableRelatedFailure ExecutableError
63+
| ExecutableRelatedFailure SomeException
6464
| FileRelatedFailure IOException
6565
| NodeExecutableError (Doc Ann)
6666
| NodeAddressAlreadyInUseError (Doc Ann)
@@ -144,8 +144,8 @@ startNode tp node ipv4 port _testnetMagic nodeCmd = GHC.withFrozenCallStack $ do
144144
let socketAbsPath = H.sprocketSystemName sprocket
145145

146146
nodeProcess
147-
<- firstExceptT ExecutableRelatedFailure
148-
$ hoistExceptT liftIO $ procNode $ mconcat
147+
<- newExceptT . fmap (first ExecutableRelatedFailure) . try
148+
$ procNode $ mconcat
149149
[ nodeCmd
150150
, [ "--socket-path", H.sprocketArgumentName sprocket
151151
, "--port", show port

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Node/Shutdown.hs

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -145,17 +145,16 @@ hprop_shutdown = integrationRetryWorkspace 2 "shutdown" $ \tempAbsBasePath' -> H
145145

146146
-- Run cardano-node with pipe as stdin. Use 0 file descriptor as shutdown-ipc
147147

148-
eRes <- H.evalIO . runExceptT $ procNode
149-
[ "run"
150-
, "--config", tempAbsPath' </> "configuration.yaml"
151-
, "--topology", tempAbsPath' </> "mainnet-topology.json"
152-
, "--database-path", tempAbsPath' </> "db"
153-
, "--socket-path", IO.sprocketArgumentName sprocket
154-
, "--host-addr", "127.0.0.1"
155-
, "--port", show @Int port
156-
, "--shutdown-ipc", "0"
157-
]
158-
res <- H.evalEither eRes
148+
res <- procNode
149+
[ "run"
150+
, "--config", tempAbsPath' </> "configuration.yaml"
151+
, "--topology", tempAbsPath' </> "mainnet-topology.json"
152+
, "--database-path", tempAbsPath' </> "db"
153+
, "--socket-path", IO.sprocketArgumentName sprocket
154+
, "--host-addr", "127.0.0.1"
155+
, "--port", show @Int port
156+
, "--shutdown-ipc", "0"
157+
]
159158
let process = res { IO.std_in = IO.CreatePipe
160159
, IO.std_out = IO.UseHandle hNodeStdout
161160
, IO.std_err = IO.UseHandle hNodeStderr

0 commit comments

Comments
 (0)