1
+ {-# LANGUAGE BlockArguments #-}
2
+ {-# LANGUAGE CPP #-}
1
3
{-# LANGUAGE GADTs #-}
2
4
{-# LANGUAGE LambdaCase #-}
3
5
{-# LANGUAGE NamedFieldPuns #-}
6
+ {-# LANGUAGE RecordWildCards #-}
4
7
{-# LANGUAGE ScopedTypeVariables #-}
5
-
8
+ {-# LANGUAGE StandaloneDeriving #-}
6
9
{-# OPTIONS_GHC -Wno-all-missed-specialisations -Wno-orphans #-}
7
10
8
11
module Cardano.Benchmarking.Command
@@ -12,26 +15,58 @@ module Cardano.Benchmarking.Command
12
15
)
13
16
where
14
17
18
+ #if !defined(mingw32_HOST_OS)
19
+ #define UNIX
20
+ #endif
21
+
15
22
import Cardano.Benchmarking.Compiler (compileOptions )
23
+ import Cardano.Benchmarking.LogTypes (AsyncBenchmarkControl (.. ), BenchTracers (.. ),
24
+ EnvConsts (.. ), TraceBenchTxSubmit (.. ))
16
25
import Cardano.Benchmarking.Script (parseScriptFileAeson , runScript )
17
26
import Cardano.Benchmarking.Script.Aeson (parseJSONFile , prettyPrint )
27
+ import Cardano.Benchmarking.Script.Env as Env (emptyEnv , newEnvConsts )
18
28
import Cardano.Benchmarking.Script.Selftest (runSelftest )
19
29
import Cardano.Benchmarking.Version as Version
20
30
import Cardano.TxGenerator.PlutusContext (readScriptData )
21
31
import Cardano.TxGenerator.Setup.NixService
22
32
import Cardano.TxGenerator.Types (TxGenPlutusParams (.. ))
23
- import Ouroboros.Network.NodeToClient (withIOManager )
24
-
25
- import Prelude
26
-
27
33
import Data.Aeson (fromJSON )
28
34
import Data.ByteString.Lazy as BSL
29
35
import Data.Foldable (for_ )
30
36
import Data.Maybe (catMaybes )
37
+ import Data.Text as T
31
38
import Data.Text.IO as T
32
39
import Options.Applicative as Opt
40
+ import Ouroboros.Network.NodeToClient (IOManager , withIOManager )
41
+
33
42
import System.Exit
34
43
44
+ #ifdef UNIX
45
+ import Cardano.Logging as Tracer (traceWith )
46
+ import Control.Concurrent as Conc (killThread , myThreadId )
47
+ import Control.Concurrent as Weak (mkWeakThreadId )
48
+ import Control.Concurrent.Async as Async (cancelWith )
49
+ import Control.Concurrent.STM as STM (readTVar )
50
+ import Control.Monad.STM as STM (atomically )
51
+ import Data.Foldable as Fold (forM_ )
52
+ import Data.List as List (unwords )
53
+ import Data.Time.Format as Time (defaultTimeLocale , formatTime )
54
+ import Data.Time.Clock.System as Time (getSystemTime , systemToUTCTime )
55
+ import GHC.Weak as Weak (deRefWeak )
56
+
57
+ import System.Posix.Signals as Sig (Handler (CatchInfo ),
58
+ SignalInfo (.. ), SignalSpecificInfo (.. ), installHandler ,
59
+ sigINT , sigTERM )
60
+ #if MIN_VERSION_base(4,18,0)
61
+ import Data.Maybe as Maybe (fromMaybe )
62
+ import GHC.Conc.Sync as Conc (threadLabel )
63
+ #endif
64
+ #endif
65
+
66
+ #ifdef UNIX
67
+ deriving instance Show SignalInfo
68
+ deriving instance Show SignalSpecificInfo
69
+ #endif
35
70
36
71
data Command
37
72
= Json FilePath
@@ -41,17 +76,22 @@ data Command
41
76
| VersionCmd
42
77
43
78
runCommand :: IO ()
44
- runCommand = withIOManager $ \ iocp -> do
79
+ runCommand = withIOManager runCommand'
80
+
81
+ runCommand' :: IOManager -> IO ()
82
+ runCommand' iocp = do
83
+ envConsts <- installSignalHandler
45
84
cmd <- customExecParser
46
85
(prefs showHelpOnEmpty)
47
86
(info commandParser mempty )
48
87
case cmd of
49
- Json file -> do
50
- script <- parseScriptFileAeson file
51
- runScript script iocp >>= handleError
52
- JsonHL file nodeConfigOverwrite cardanoTracerOverwrite -> do
53
- opts <- parseJSONFile fromJSON file
88
+ Json actionFile -> do
89
+ script <- parseScriptFileAeson actionFile
90
+ runScript emptyEnv script envConsts >>= handleError . fst
91
+ JsonHL nixSvcOptsFile nodeConfigOverwrite cardanoTracerOverwrite -> do
92
+ opts <- parseJSONFile fromJSON nixSvcOptsFile
54
93
finalOpts <- mangleTracerConfig cardanoTracerOverwrite <$> mangleNodeConfig nodeConfigOverwrite opts
94
+ let consts = envConsts { envNixSvcOpts = Just finalOpts }
55
95
56
96
Prelude. putStrLn $
57
97
" --> initial options:\n " ++ show opts ++
@@ -60,20 +100,85 @@ runCommand = withIOManager $ \iocp -> do
60
100
quickTestPlutusDataOrDie finalOpts
61
101
62
102
case compileOptions finalOpts of
63
- Right script -> runScript script iocp >>= handleError
64
- err -> handleError err
103
+ Right script -> runScript emptyEnv script consts >>= handleError . fst
104
+ err -> die $ " tx-generator:Cardano.Command.runCommand JsonHL: " ++ show err
65
105
Compile file -> do
66
106
o <- parseJSONFile fromJSON file
67
107
case compileOptions o of
68
108
Right script -> BSL. putStr $ prettyPrint script
69
- err -> handleError err
70
- Selftest outFile -> runSelftest iocp outFile >>= handleError
109
+ Left err -> die $ " tx-generator:Cardano.Command.runCommand Compile: " ++ show err
110
+ Selftest outFile -> runSelftest emptyEnv envConsts outFile >>= handleError
71
111
VersionCmd -> runVersionCommand
72
112
where
73
113
handleError :: Show a => Either a b -> IO ()
74
114
handleError = \ case
75
115
Right _ -> exitSuccess
76
- Left err -> die $ show err
116
+ Left err -> die $ " tx-generator:Cardano.Command.runCommand handleError: " ++ show err
117
+ installSignalHandler :: IO EnvConsts
118
+ installSignalHandler = do
119
+ -- The main thread does not appear in the set of asyncs.
120
+ wkMainTID <- Weak. mkWeakThreadId =<< myThreadId
121
+ envConsts@ EnvConsts { .. } <- STM. atomically $ newEnvConsts iocp Nothing
122
+ abc <- STM. atomically $ STM. readTVar envThreads
123
+ _ <- pure (abc, wkMainTID)
124
+ #ifdef UNIX
125
+ let signalHandler = Sig. CatchInfo signalHandler'
126
+ signalHandler' sigInfo = do
127
+ tid <- Conc. myThreadId
128
+ utcTime <- Time. systemToUTCTime <$> Time. getSystemTime
129
+ -- It's meant to match Cardano.Tracers.Handlers.Logs.Utils
130
+ -- The hope was to avoid the package dependency.
131
+ let formatTimeStamp = formatTime' " %Y-%m-%dT%H-%M-%S"
132
+ formatTime' = Time. formatTime Time. defaultTimeLocale
133
+ timeStamp = formatTimeStamp utcTime
134
+ #if MIN_VERSION_base(4,18,0)
135
+ maybeLabel <- Conc. threadLabel tid
136
+ let labelStr' :: String
137
+ labelStr' = fromMaybe " (thread label unset)" maybeLabel
138
+ #else
139
+ labelStr' = " (base version insufficient to read thread label)"
140
+ #endif
141
+ labelStr :: String
142
+ labelStr = List. unwords [ timeStamp
143
+ , labelStr'
144
+ , show tid
145
+ , " received signal"
146
+ , show sigInfo ]
147
+ errorToThrow :: IOError
148
+ errorToThrow = userError labelStr
149
+ tag = TraceBenchTxSubError . T. pack
150
+ traceWith' msg = do
151
+ mBenchTracer <- STM. atomically do readTVar benchTracers
152
+ case mBenchTracer of
153
+ Nothing -> pure ()
154
+ Just tracers -> do
155
+ let wrappedMsg = tag msg
156
+ submittedTracers = btTxSubmit_ tracers
157
+ Tracer. traceWith submittedTracers wrappedMsg
158
+
159
+ Prelude. putStrLn labelStr
160
+ traceWith' labelStr
161
+ mABC <- STM. atomically $ STM. readTVar envThreads
162
+ case mABC of
163
+ Nothing -> do
164
+ -- Catching a signal at this point makes it a higher than
165
+ -- average risk of the tracer not being initialized, so
166
+ -- this pursues some alternatives.
167
+ let errMsg = " Signal received before AsyncBenchmarkControl creation."
168
+ Prelude. putStrLn errMsg
169
+ traceWith' errMsg
170
+ Just AsyncBenchmarkControl { .. } -> do
171
+ abcFeeder `Async.cancelWith` errorToThrow
172
+ Fold. forM_ abcWorkers \ work -> do
173
+ work `Async.cancelWith` errorToThrow
174
+ -- The main thread does __NOT__ appear in the above list.
175
+ -- In order to kill that off, this, or some equivalent,
176
+ -- absolutely /must/ be done separately.
177
+ mapM_ Conc. killThread =<< Weak. deRefWeak wkMainTID
178
+ Fold. forM_ [Sig. sigINT, Sig. sigTERM] $ \ sig ->
179
+ Sig. installHandler sig signalHandler Nothing
180
+ #endif
181
+ pure envConsts
77
182
78
183
mangleNodeConfig :: Maybe FilePath -> NixServiceOptions -> IO NixServiceOptions
79
184
mangleNodeConfig fp opts = case (getNodeConfigFile opts, fp) of
0 commit comments