Treating POSIX signals as exceptions?
David Roundy
droundy at abridgegame.org
Sat Nov 15 10:15:38 EST 2003
On Fri, Nov 14, 2003 at 10:51:59PM +0100, Wolfgang Thaller wrote:
>
> On Tue, Nov 11, 2003 at 09:39:05AM -0000, Simon Marlow wrote:
> >Hmm, there is clearly a choice between having a signal spawn a new
> >thread or raise an asynchronous exception, and it's not at all clear
> >which is best.
> >
> >But, since we can implement either using the other one, it doesn't
> >really matter too much which one is primitive.
>
> How can the spawn-a-thread semantics be implemented using asynchronous
> exceptions? Doesn't the thread that the exception is thrown to unwind to
> the topmost handler?
You'd create a thread specifically for handling exceptions when you add
your handler.
> On 14.11.2003, at 16:21, David Roundy wrote:
> >In darcs, I really have no interest in dealing with signals, I just want
> >to make sure my temporary files are cleaned up even if the user hits ^C.
> >If the default signal handler uses exceptions, this will happen for
> >free. Currently, my only choice for the former purpose is to use
> >something like withSignal.
>
> But the ^C signal itself is not, in general, sent to a specific thread;
> rather, it's sent to the whole process. So while it's reasonable to
> convert a SIGINT to an asynchronous exception thrown to a specific thread
> (as GHCi does), I don't see how that can be done generally. If you want
> bracket to clean up if the user hits ^C, you'd still have to hava a way
> of specifying which thread(s) get aborted using an exception on SIGINT.
> The default behaviour should lead to termination of the entire program;
> but in other situations (like GHCi for example), I'd probably want to
> catch the exception in one thread and have all other threads continue.
This doesn't seem like a problem. By default the exception goes to main
(which aborts the whole program), and if you want to change which thread
gets the exception that's fine.
> >I guess the problem is that as far as I can tell, there is no way to
> >implement a "correct" bracket along with the existing POSIX signal
> >implementation, since there's no way to find out what the current
> >handler is, which means bracket can't install its own handler without
> >messing up the current handler.
>
> A way to find out the current handler could probably be added, but it'd
> still be impossible to implement a SIGINT-aware bracket because signal
> handlers are per-process, not per-thread.
Well, bracket doesn't work with concurrent programs even in the absense of
signals (except in the main thread) so you don't lose anything there. If
you write a concurrent program and want its threads to clean up, you always
have to code that yourself, for example using a bracket in the main thread.
> >It still doesn't do what I'd really like, which is add default handlers
> >for signals. I'd really like a
> >
> >withSignalsAsExceptions :: IO a -> IO a
> >
> >which would add an exception-throwing handler for *every* signal type
> >(perhaps every asynchronous signal type...), and then run the default
> >handler for any uncaught signals. Even better if main was automatically
> >run in a withSignalsAsExceptions environment.
>
> Wouldn't that render every signal that isn't intended to cause clean
> program shutdown next to useless? It seems perfect for SIGINT and
> SIGTERM, but I don't think that I'd want to handle SIGCONT or SIGCHLD as
> exceptions.
You're right. I was only thinking of exceptions that terminate, so you'd
only want to throw exceptions for sigHUP, sigINT, sigALRM, sigTERM and
possibly sigUSR1 and sigUSR2.
I'm attaching the signal handling code I now actually use. It makes no
provision for concurrency because I don't use any concurrency (although I
do use pthreads). Actually, although I export catchSignal and throwSignal
on matter of principle, I don't use them either. I just use
main = withSignalsHandled $ do ...
which does all I want done.
--
David Roundy
http://www.abridgegame.org
-------------- next part --------------
% Copyright (C) 2003 David Roundy
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU General Public License as published by
% the Free Software Foundation; either version 2, or (at your option)
% any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU General Public License
% along with this program; if not, write to the Free Software Foundation,
% Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
\begin{code}
module SignalHandler ( withSignalsHandled, catchSignal, throwSignal,
) where
import System.Exit ( exitWith, ExitCode ( ExitFailure ) )
import Control.Concurrent ( myThreadId )
import Control.Exception ( catchDyn, throwDyn, throwDynTo )
import Data.Dynamic ( Typeable )
import Posix ( installHandler, Handler(..), Signal,
sigINT, sigHUP, sigABRT, sigALRM, sigTERM,
)
\end{code}
\begin{code}
newtype SignalException = SignalException Signal deriving (Typeable)
withSignalsHandled :: IO a -> IO a
withSignalsHandled job = do
id <- myThreadId
sequence_ $ map (ih id) [sigINT, sigHUP, sigABRT, sigALRM, sigTERM]
job `catchSignal` defaults
where defaults s | s == sigINT = ew "Interrupted!"
| s == sigHUP = ew "HUP"
| s == sigABRT = ew "ABRT"
| s == sigALRM = ew "ALRM"
| s == sigTERM = ew "TERM"
| otherwise = ew "Unhandled signal!"
ew s = do putStrLn s
exitWith $ ExitFailure $ -1
ih id s = installHandler s (Catch $ throwDynTo id $ SignalException s) Nothing
catchSignal :: IO a -> (Signal -> IO a) -> IO a
catchSignal job handler =
job `Control.Exception.catchDyn` (\(SignalException sig) -> handler sig)
throwSignal :: Signal -> IO a
throwSignal s = Control.Exception.throwDyn (SignalException s)
\end{code}
More information about the Libraries
mailing list