{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
module Lambdabot.Util.Signals
( Signal
, SignalException(..)
, ircSignalMessage
, withIrcSignalCatch
) where
import Data.Typeable
import Control.Exception (Exception)
#ifdef mingw32_HOST_OS
import Control.Monad.Trans.Control
type Signal = String
newtype SignalException = SignalException Signal deriving (Show, Typeable)
instance Exception SignalException
ircSignalMessage :: Signal -> [Char]
ircSignalMessage s = s
withIrcSignalCatch :: MonadBaseControl IO m => m a -> m a
withIrcSignalCatch m = m
#else
import Control.Concurrent.Lifted (myThreadId, newEmptyMVar, putMVar, MVar, ThreadId)
import Control.Exception.Lifted (bracket, throwTo)
import Control.Monad
import Control.Monad.Base
import Control.Monad.Trans.Control
import System.IO.Unsafe
import System.Posix.Signals
newtype SignalException = SignalException Signal deriving (Show, Typeable)
instance Exception SignalException
withHandler :: MonadBaseControl IO m => Signal -> Handler -> m a -> m a
withHandler s h m = bracket
(liftBase (installHandler s h Nothing))
(liftBase . flip (installHandler s) Nothing)
(const m)
withHandlerList :: MonadBaseControl IO m => [Signal] -> (Signal -> Handler) -> m a -> m a
withHandlerList sl h m = foldr (withHandler `ap` h) m sl
ircSignalsToCatch :: [(Signal, String)]
ircSignalsToCatch =
[ (busError, "SIGBUS" )
, (segmentationViolation, "SIGSEGV" )
, (keyboardSignal, "SIGINT" )
, (softwareTermination, "SIGTERM" )
, (keyboardTermination, "SIGQUIT" )
, (lostConnection, "SIGHUP" )
, (internalAbort, "SIGABRT" )
]
ircSignalMessage :: Signal -> String
ircSignalMessage sig = case lookup sig ircSignalsToCatch of
Just sigName -> sigName
Nothing -> "killed by unknown signal"
ircSignalHandler :: ThreadId -> Signal -> Handler
ircSignalHandler threadid s
= CatchOnce $ do
putMVar catchLock ()
releaseSignals
throwTo threadid $ SignalException s
releaseSignals :: IO ()
releaseSignals = sequence_
[ installHandler sig Default Nothing
| (sig, _) <- ircSignalsToCatch
]
{-# NOINLINE catchLock #-}
catchLock :: MVar ()
catchLock = unsafePerformIO newEmptyMVar
withIrcSignalCatch :: MonadBaseControl IO m => m a -> m a
withIrcSignalCatch m = do
_ <- liftBase $ installHandler sigPIPE Ignore Nothing
_ <- liftBase $ installHandler sigALRM Ignore Nothing
threadid <- myThreadId
withHandlerList (map fst ircSignalsToCatch) (ircSignalHandler threadid) m
#endif