Skip to content

Commit

Permalink
launcher: When terminated, ensure child processes are cleaned up
Browse files Browse the repository at this point in the history
  • Loading branch information
rvl committed Mar 18, 2019
1 parent 2c90f8f commit dd8933f
Show file tree
Hide file tree
Showing 5 changed files with 71 additions and 4 deletions.
16 changes: 13 additions & 3 deletions app/Cardano/Launcher.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}

-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
Expand All @@ -10,6 +12,7 @@ module Cardano.Launcher
( Command (..)
, ProcessHasExited(..)
, launch
, installSignalHandlers
) where

import Prelude
Expand All @@ -27,6 +30,13 @@ import System.Exit
import System.Process
( proc, waitForProcess, withCreateProcess )

#ifdef mingw32_HOST_OS
import Cardano.Launcher.Windows
( installSignalHandlers )
#else
import Cardano.Launcher.POSIX
( installSignalHandlers )
#endif

data Command = Command
{ cmdName :: String
Expand Down Expand Up @@ -73,6 +83,6 @@ launch cmds = do
throwIO $ ProcessHasExited name code
case res of
Left e -> return e
Right _ -> error
"Unreachable. Supervising threads should never finish. \
\They should stay running or throw @ProcessHasExited@."
Right _ -> error $
"Unreachable. Supervising threads should never finish. " <>
"They should stay running or throw @ProcessHasExited@."
33 changes: 33 additions & 0 deletions app/Cardano/Launcher/POSIX.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,33 @@
-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
-- Portability: POSIX
--

module Cardano.Launcher.POSIX
( installSignalHandlers
) where

import Prelude

import Control.Monad
( void )
import Say
( sayErr )
import System.Posix.Signals
( Handler (..)
, installHandler
, keyboardSignal
, raiseSignal
, softwareTermination
)

-- | Convert any SIGTERM received to SIGINT, for which the runtime system has
-- handlers that will correctly clean up sub-processes.
installSignalHandlers :: IO ()
installSignalHandlers = void $
installHandler softwareTermination termHandler Nothing
where
termHandler = CatchOnce $ do
sayErr "Terminated by signal."
raiseSignal keyboardSignal
15 changes: 15 additions & 0 deletions app/Cardano/Launcher/Windows.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
-- Portability: Windows
--

module Cardano.Launcher.Windows
( installSignalHandlers
) where

import Prelude

-- | Stub function for windows.
installSignalHandlers :: IO ()
installSignalHandlers = pure ()
4 changes: 3 additions & 1 deletion app/launcher/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,8 @@ import Prelude
import Cardano.CLI
( Network, Port, decode, encode, getArg )
import Cardano.Launcher
( Command (Command), ProcessHasExited (ProcessHasExited), launch )
( Command (Command), ProcessHasExited (ProcessHasExited), launch
, installSignalHandlers )
import Control.Concurrent
( threadDelay )
import Control.Monad
Expand Down Expand Up @@ -59,6 +60,7 @@ main = do
network <- getArg args cli (longOption "network") decode

sayErr "Starting..."
installSignalHandlers
let commands =
[ nodeHttpBridgeOn bridgePort
, walletOn walletPort bridgePort network
Expand Down
7 changes: 7 additions & 0 deletions cardano-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -183,6 +183,13 @@ executable cardano-wallet-launcher
other-modules:
Cardano.CLI
Cardano.Launcher
if os(windows)
build-depends: Win32
other-modules: Cardano.Launcher.Windows
else
build-depends: unix
other-modules: Cardano.Launcher.POSIX

main-is:
Main.hs

Expand Down

0 comments on commit dd8933f

Please sign in to comment.