RE: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-11 Thread Simon Marlow
On 10 April 2006 22:19, John Meacham wrote:
 On Fri, Apr 07, 2006 at 02:58:01PM +0100, Simon Marlow wrote:
 According to your definition of exitWith above, I can't both raise an
 exception *and* exit in the same thread.  If I register an onExit
 handler that throws an exception to the current thread, things go
 wrong if the current thread also calls exitWith.  Also, you couldn't
 call exitWith while holding an MVar, if the handlers need access to
 the same MVar.
 
 hrm? nothing goes wrong. it is the same as calling 'throw' in the
 current thread.

Your code for exitWith:

exitWith status = do
takeMVar exitMVar -- winner takes all
let handleLoop = do
hs - swapMVar handlerMVar []
sequence_ hs
if null hs then return () else handleLoop
handleLoop
exitWith_ status

now If I have a handler registered that throws an exception to the
current thread, what happens?  handleLoop is aborted, the exception is
propagated to the top level of the thread, where the top-level exception
handler calls exitWith again, and promptly deadlocks because exitMVar is
already empty.

In the interests of keeping the discussion manageable, I'll deal with
the rest of the points later.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 08:54:32AM +0100, Simon Marlow wrote:
 now If I have a handler registered that throws an exception to the
 current thread, what happens?  handleLoop is aborted, the exception is
 propagated to the top level of the thread, where the top-level exception
 handler calls exitWith again, and promptly deadlocks because exitMVar is
 already empty.

True, the handlers probably should run in their own thread then. hmm..
will think more on these issues...

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-11 Thread David Roundy
On Mon, Apr 10, 2006 at 02:19:23PM -0700, John Meacham wrote:
 On Mon, Apr 10, 2006 at 02:58:20PM +0100, Simon Marlow wrote:
  Suppose I want to do some action with a temporary file:
  
 bracket
 newTempFile
 (\f - removeTempFile f)
 (\f - doSomethingWith f)
  
  Under your scheme, this code doesn't get to remove its temporary file on
  exit, unless I explicitly add an exit handler that throws an exception
  to the current thread.
  
  I think code like the above should just work.  Furthermore, I think it
  should be an invariant that a thread is never discarded or killed, only
  sent an exception.  Otherwise, how else can I acquire a resource and
  guarantee to release it when either an exception is raised, the program
  exits, or the computation completes?
 
 you ask the system to send you an exception on exit.

(As I'm sure you are aware) I'm with Simon on this one.  The default
cleanup handling should just work, and you shouldn't need to write
special-case code in order to properly clean up.  Having exitWith throw
exceptions (as it currently does in ghc) is very nice.

Perhaps we could have a special sort of thread that is just killed upon
exit with no exceptions being raised, but I wouldn't be tempted to use such
a thread... unless I suppose I had some unimportant long-running ffi call
to make, and didn't want exiting to be slowed down by waiting for it to
complete.  It would definitely be nice to have interruptible ffi calls (and
not just interruptible by exiting), but I'm not really sure how one would
go about that.
-- 
David Roundy
http://www.darcs.net
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-10 Thread John Meacham
On Mon, Apr 10, 2006 at 02:58:20PM +0100, Simon Marlow wrote:
 Suppose I want to do some action with a temporary file:
 
bracket
newTempFile
(\f - removeTempFile f)
(\f - doSomethingWith f)
 
 Under your scheme, this code doesn't get to remove its temporary file on
 exit, unless I explicitly add an exit handler that throws an exception
 to the current thread.
 
 I think code like the above should just work.  Furthermore, I think it
 should be an invariant that a thread is never discarded or killed, only
 sent an exception.  Otherwise, how else can I acquire a resource and
 guarantee to release it when either an exception is raised, the program
 exits, or the computation completes?

you ask the system to send you an exception on exit.

 
 According to your definition of exitWith above, I can't both raise an
 exception *and* exit in the same thread.  If I register an onExit
 handler that throws an exception to the current thread, things go wrong
 if the current thread also calls exitWith.  Also, you couldn't call
 exitWith while holding an MVar, if the handlers need access to the same
 MVar.

hrm? nothing goes wrong. it is the same as calling 'throw' in the
current thread.

I don't see how it is unsafe, it is always unsafe to call a routine that
needs an MVar you already have held open. you don't call exitWith by
accident. There is always 'forkIO exitFailure' in any case. 

 You didn't show WithTemporaryExitHandler, which complicates things quite
 a bit.

it is uneeded, only a utility routine, I just didn't want to show the
bookkeeping in the handler list to allow deletion of elements as it
wasn't important to the scheme. any thread that wants to do bracket
style cleanup just asks to be thrown an Exit exception and uses the
standard 'bracket' etc.. routines.

 Also, your implementation has a race condition - a thread might add
 another exit handler after the swapMVar.

that is why it is in a swapMVar loop, processing batch's of handlers. at
some point, you just gotta accept that another thread didn't get its
handler in on time, after all, if things were scheduled differently it
might not have gotten there. mainly I wanted to make sure no handlers
registered from within other handlers got lost, as those should run to
completion being synchronously regiseterd from the handlers point of
view.

 I think we can probably agree on one thing: exitWith should raise an
 exception:
 
   exitWith e = throw (ExitException e)

I disagree :)

throwTo and throw should raise exceptions, exit should quit the program.
though, perhaps we just need another function in the middle.

AFAICT, what you are proposing is the same as mine but with

forkIO being implemented as 

forkIO action = forkIO' action' where 
action' = do
myThreadId = onExit . throwTo PleaseExit
action

I just want to have control as to whether that throw me an exception
exit handler gets added and not have the implementation wait on my
thread to clean up before it can exit if it has nothing special to clean
up and might be deep in foreign calls.

perhaps if there were just a flag on each thread saying whether they
wanted to recieve exit message? though. I still don't like the idea of
exitWith throwing anything, just feels really dirty. though, if there
were a 'runExitHandlers' routine, what I want can be simulated by
'runExitHandlers  exitWith_ foo'


 This isn't inconsistent with your proposal, and I think it's
 unambiguously better.  The top-level exception handler catches
 ExitException and performs the required steps (running handlers, calling
 exit_).  As you said, you need a top-level exception handler anyway,
 this is just a small change to your proposal, moving the exit actions to
 the top-level exception handler.

but that means you have to wait until the thread with that top level
exception handler becomes runnable. which could take arbitrary time if
it is in a foreign call. I'd rather stuff be taken care of on the
current thread (since we know we are runnable since we just ran
exitWith), or on some new exit only thread. as if exitwith behaved as if
it were called (forkIO $ exitWith)

it just seems odd for your global system exit code to be hidden deep at
the base of a certain threads stack somewhere. I don't mind so much
exceptions being thrown everywhere to give things a chance to clean up,
so much as the requirement we wait for it to fall off the distinguished
'main thread' before the program can actually quit.

by default fork 
  3. simple rules. expressable in pure haskell.
  4. can quit immediatly on a SIGINT since the exitWith routine runs on
  whatever thread called exit, rather than throwing responsibility back
  to the other threads which might be stuck in a foreign call. (unless
  you explicitly ask it to)
 
 Don't understand this one - it certainly doesn't help with SIGINT in
 GHC.

when the signal occurs ghc sends a byte down a pipe, listening thread
reads that and calls 

RE: asynchronous exceptions

2006-04-07 Thread Simon Marlow
On 07 April 2006 00:36, Marcin 'Qrczak' Kowalczyk wrote:

 Simon Marlow [EMAIL PROTECTED] writes:
 I agree with your assessment of the problems with interruptible
 operations in GHC: that it is impossible to completely block async
 exceptions across a computation.  We could certainly add a way to
 do this.  Is that the substance of your objection to GHC's async
 exception mechanism?
 
 Regarding interruptible operations, this and one more thing that I
 haven't written there:
 
 The fact that some function uses an interruptible operation internally
 is a visible aspect of its behavior, both in GHC design and in mine.

I don't consider this to be a problem.  Every API call you make has the
potential to throw exceptions, and since we don't usually go to the
trouble of documenting every exception that every library function can
raise, the caller always has to be prepared to handle arbitrary
exceptions thrown by calls to library functions.  Asynchronous
exceptions thrown by interruptible operations just fall into this
category.

BTW, I just realised a better way to express block.  If block is
supposed to count nesting, then we have a problem that you can still
unblock exceptions even within a block by using sufficient number of
unblocks, so the right way is to give block this type:

  block :: ((IO b - IO b) - IO a) - IO a

you use it like this:

  block $ \restore - 
(do x - takeMVar m
restore (...) `catch` \e - ...)

so the only way to unblock is to restore the state of an enclosing
block.  Returning the restore function and using it outside the block
isn't dangerous, so we don't have to play any quantified type games to
prevent that.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-07 Thread Simon Marlow
On 06 April 2006 23:20, John Meacham wrote:

 I'm not proposing that we ignore signals, just that we should clearly
 delimit the platform-specific bits, perhaps by putting signal support
 into an addendum.
 
 yeah, I was thinking a separate environment addendum should be in the
 report, which takes behavior that is undefined in the language
 standard, 
 and defines it for various platforms. it wouldn't extend the
 functionality or scope of the standard, just define what couldn't be
 defined in the standard.
 
 like the standard might say the set of signals is undefined while
 the 
 UNIX addendum will say the set of signals will include at least
 SIGINT,SIGHUP,etc...

There's the question of whether ^C should look the same on both Windows
and Unix.  Windows doesn't have signals as such, but some things like ^C
can be made to look like signals.  We might consider specifying as part
of the portable part of the API that there is at least an interrupt
signal that corresponds to a user interrupt, and in the
platform-specific part of the documentation we say what it actually maps
to on each platform (SIGINT on Unix, CTRL_BREAK_EVENT on Windows, etc.).

 GHC has no support for these right now.  They're pretty tricky to
 handle, because the OS thread that caused the signal to be raised is
 stopped at some arbitrary instruction, and it would require some
 serious acrobatics to munge that OS thread into a state where it is
 possible to raise the (Haskell) exception.  I do vaguely recall that
 people have achieved this in the past, in order to use page faults
 for write barriers, that sort of thing.
 
 how does ghc handle things like divide by zero then?

By checking before trying to divide :-)

 signal an asynchronous exceptional event
 - the user should be able to choose the threads on which they wish
   to catch these, those that need to clean up after themselves.
 
 inform the app of an event it might want to take note of
 - these should run on their own thread, concurrently to all other
   threads
 
 GHC directly support the latter version, and you can implement the
 former with a little extra code and a global variable.  I think it
 would be nice to do as you suggest and provide a way to have the
 async signals turn directly into exceptions.
 
 One problem, though, is that because we can't interrupt a foreign
 call with an async exception, ^C can be rather unresponsive. 
 Perhaps I should look into this and see whether it would be possible
 in GHC for a concurrent foreign call to be interruptible; it would
 involve terminating the foreign call somehow (pthread_cancel?)
 before raising the exception.  We can't do this in a bound thread,
 however. 
 
 You should be able to handle the SIGINT imediatly no matter whether
 foregin code is running if your handler is in its own thread right?

Yes, but if the signal handler wants to send an exception to the main
thread, as it often does, and the main thread is in a foreign call, ^C
appears to not do anything.

 just have the C signal handler write a byte to a pipe, your haskell
 signal handler thread is in a
 
 repeatM $ do
 readExactlyOneByte
 signalHandler
 
 loop.

Yes, this is exactly what GHC does.


 = minimal proposal =
 
 I think a good minimal solution will be the following, it neatly
 avoids 
 turning signals into exceptions, which may be problematic, but
 provides 
 for the common cases of signal usages while being compatible with both
 cooperative and SMP systems.
 
 == catching signals ==
 
 implementations provide a way of catching signals such that the
 handler 
 runs as if in its own thread. something like the following
 
 data SigInfo = ...
 data HandlerType = SigOneShot | SigReset | SigIdempotent
 
 data SigAction = SigAction {
 signalType :: HandlerType,
 signalAction :: SigInfo - IO ()
 }  | SigDefault | SigIgnore | SigExit (SigInfo - ExitStatus)
 
 installHandler :: Signal - SigAction - IO SigAction
 installHandler = ...

 the action runs in its own thread.

Yes, looks quite reasonable.
 
 == on exit ==

I'll address this in a separate thread.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-07 Thread Simon Marlow
On 07 April 2006 13:24, David Roundy wrote:

 The catch to this [no pun intended]
 is that when the main thread exits all other threads are silently
 terminated, without the chance to clean up...

This is a mistake in GHC, I think.  When someone calls exit, or when the
main thread exits, all the other threads in the system should be send
exceptions too. 

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-07 Thread Simon Marlow
On 07 April 2006 13:58, John Meacham wrote:

 all threads keep running while the exit handers are running, all
 blockExit would do is grab and release an MVar. exit itself takes
 that MVar on starting to get rid of races to exit as well as protect
 itsesf from 'blockExit' (but won't ever put the MVar back).

That sounds hard to program with - surely you want to stop the program
in order to clean up?  Otherwise the program is going to continue
working, generating more exit handlers, and we might never get to exit.


Of course you could implement some global flag to say that an exit is in
progress, but that implies explicit checking of the flag all over the
place, which is what asynchronous exceptions are designed to avoid.

When *do* we exit, in fact?  When all the exit handlers have finished?

 Exceptions are the right way to handle releasing resources, and they
 are the right way to register cleanup actions.  Therefore I believe
 exceptions are the right way to handle cleaning up on exit, too.
 
 Well, We really need 'onExit' for other reasons as well, I think it
 should make it into the standard independently.

Sure, I'm happy with onExit.

 I think you have that backwards, releasing resources is the right
 thing 
 to do when you get an exception, but there are lots of other reasons
 you 
 want to release resources that have nothing to do with exceptions. you
 don't use 'throwTo' to close all your files :)

No, but you do use an exception handler, or something built using
exception handlers like 'finally'.  I don't want to have to use *both*
exception handlers and exit handlers.

 Since async exceptions are no problem to implement in a coop system,
 shouldn't we use them for exit too?
 
 but then only one thread gets to clean up after itself,

I think all threads should get the exit exception (I know GHC doesn't
currently do this).

 and you have
 the issue that you can't interrupt a foreign function by throwing to
 it. 

The situation is the same as in your proposal - the foreign call
continues running.  However, as soon as it returns, the Haskell thread
will receive an exception.

I propose this:

  When System.Exit.exitWith is called, all currently running
  threads are sent an exit exception as soon as possible.
  Exit handlers registered with onExit are started immediately.
  The system exits when (a) the main thread has stopped, and (b)
  all exit handlers have completed.  Subsequent calls to exitWith
  simply throw an exit exception in the current thread.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: asynchronous exceptions

2006-04-07 Thread Marcin 'Qrczak' Kowalczyk
Simon Marlow [EMAIL PROTECTED] writes:

 BTW, I just realised a better way to express block.  If block is
 supposed to count nesting, then we have a problem that you can still
 unblock exceptions even within a block by using sufficient number of
 unblocks, so the right way is to give block this type:

   block :: ((IO b - IO b) - IO a) - IO a

Or perhaps:
block :: ((forall b. IO b - IO b) - IO a) - IO a

It doesn't fit classic mutexes and conditions with my semantics of
implicit blocking, because condition wait should restore the blocking
state to the one before taking the mutex - but the condition wait is
written without explicit passing of any value from the point of taking
the mutex.

I'm not sure how it carries over to Haskell patterns though.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-07 Thread John Meacham
On Fri, Apr 07, 2006 at 02:58:01PM +0100, Simon Marlow wrote:
 Of course you could implement some global flag to say that an exit is in
 progress, but that implies explicit checking of the flag all over the
 place, which is what asynchronous exceptions are designed to avoid.
 
 When *do* we exit, in fact?  When all the exit handlers have finished?

I think we might be thinking of different things. here is a complete
implementation of exit.

exitMVar :: MVar () -- starts full
exitMVar = ..

handlerMVar :: MVar [IO ()]  -- starts with []
handlerMVar = ...

onExit :: IO () - IO ()
onExit action = modifyMVar handlerMVar (action:)

exitWith status = do
takeMVar exitMVar -- winner takes all
let handleLoop = do
hs - swapMVar handlerMVar []
sequence_ hs
if null hs then return () else handleLoop
handleLoop
exitWith_ status

exitWith_ calls the underlying 'exit' routine of the operating system
immediatly. no waiting.

I'll get to why you can't have handlers building up indefinitly below.

  I think you have that backwards, releasing resources is the right
  thing 
  to do when you get an exception, but there are lots of other reasons
  you 
  want to release resources that have nothing to do with exceptions. you
  don't use 'throwTo' to close all your files :)
 
 No, but you do use an exception handler, or something built using
 exception handlers like 'finally'.  I don't want to have to use *both*
 exception handlers and exit handlers.

they serve different purposes. You might use both at different places in
the same program, but never for the same resource. 

 The situation is the same as in your proposal - the foreign call
 continues running.  However, as soon as it returns, the Haskell thread
 will receive an exception.
 
 I propose this:
 
   When System.Exit.exitWith is called, all currently running
   threads are sent an exit exception as soon as possible.
   Exit handlers registered with onExit are started immediately.
   The system exits when (a) the main thread has stopped, and (b)
   all exit handlers have completed.  Subsequent calls to exitWith
   simply throw an exit exception in the current thread.

this seems the wrong way round. exitWith is something you call in
_response_ to an exception, telling the program you want to exit. not
something that generates an exception. In particular, you often won't
know what 'status' to exit with until you have had everything clean up
properly (or fail to clean up properly). We have 'throwTo' to throw
exceptions around.

what I would expect from dealing with other languages is:

exitWith does as it does above in my example, nothing more, nothing
less. in particular it is not special in any way when it comes to
exceptions or concurrency other than using standard MVars.


falling off the end of the main thread is equivalent to calling
exitWith Success, an exception falling off the end is equivalent to
exitWith Failure.

the main thread is not special in any way other than being wrappen in
the equivalent of.

-- user written main function
main = do ...

-- what the implementation uses as its main thread
realMain = catch (\_ - exitFailure) main  exitSuccess


if you want to die and clean up via exceptions, use 'throwTo' to throw a
'PleaseExit' exception to whatever threads you like.

if you are writing a library that uses threads internally, where you
have a particular thread you want to clean up via exceptions, do an

myThreadId = onExit . throwTo PleaseExit

now you will get an exception on exit. if you need the exit to wait
until you complete something, you can have your handler wait on an MVar.

advantages of this set up.

1. base case requires no concurrency or exceptions
2. abstract threads possible, if you don't let your ThreadId escape,
there is no way to get an exception you don't bring upon yourself.
3. simple rules. expressable in pure haskell.
4. can quit immediatly on a SIGINT since the exitWith routine runs on
whatever thread called exit, rather than throwing responsibility back to
the other threads which might be stuck in a foreign call. (unless you
explicitly ask it to)
5. you don't have to worry about 'PleaseExit' if you don't want to.
6. modularity modularity. now that concurrency is part of the standard,
we will likely see a lot of libraries using concurrency internally for
little things that it wants to keep abstract, or concurrent programs
composed with each other. having a global 'throw something to all
threads on the system' doesn't feel right.
7. subsumes the exitWith throws exceptions everywhere policy.

John







-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-06 Thread John Meacham
On Wed, Apr 05, 2006 at 03:41:55PM +0100, Simon Marlow wrote:
  I have been giving signals some thought, and resarching what other
  languages do, and have a semi-proposal-maybe.
 
 We should be careful here: the Haskell standard has so far remained
 platform-independent, and I think it would be nice to keep it that way.

Signals arn't as bad as some things, as a platform that doesn't support
signals would just be visibly the same as one where the signals never
happen to be generated. in any case, a signal-safe haskell program will
be portable.

assuming we don't make the ability to _send_ a signal part of the
standard.

 I'm not proposing that we ignore signals, just that we should clearly
 delimit the platform-specific bits, perhaps by putting signal support
 into an addendum.

yeah, I was thinking a separate environment addendum should be in the
report, which takes behavior that is undefined in the language standard,
and defines it for various platforms. it wouldn't extend the
functionality or scope of the standard, just define what couldn't be
defined in the standard.

like the standard might say the set of signals is undefined while the
UNIX addendum will say the set of signals will include at least
SIGINT,SIGHUP,etc...

 GHC has no support for these right now.  They're pretty tricky to
 handle, because the OS thread that caused the signal to be raised is
 stopped at some arbitrary instruction, and it would require some serious
 acrobatics to munge that OS thread into a state where it is possible to
 raise the (Haskell) exception.  I do vaguely recall that people have
 achieved this in the past, in order to use page faults for write
 barriers, that sort of thing.

how does ghc handle things like divide by zero then?

 
 SIGPIPE is possibly easier than the others.  SIGFPE you can usually turn
 off in favour of exceptional values instead.

yeah, I was thinking we should make these the default in the unix
addendum.

  signal an asynchronous exceptional event
  - the user should be able to choose the threads on which they wish to
catch these, those that need to clean up after themselves.
  
  inform the app of an event it might want to take note of
  - these should run on their own thread, concurrently to all other
threads
 
 GHC directly support the latter version, and you can implement the
 former with a little extra code and a global variable.  I think it would
 be nice to do as you suggest and provide a way to have the async signals
 turn directly into exceptions.

 One problem, though, is that because we can't interrupt a foreign call
 with an async exception, ^C can be rather unresponsive.  Perhaps I
 should look into this and see whether it would be possible in GHC for a
 concurrent foreign call to be interruptible; it would involve
 terminating the foreign call somehow (pthread_cancel?) before raising
 the exception.  We can't do this in a bound thread, however.

You should be able to handle the SIGINT imediatly no matter whether
foregin code is running if your handler is in its own thread right?

just have the C signal handler write a byte to a pipe, your haskell
signal handler thread is in a 

repeatM $ do
readExactlyOneByte
signalHandler

loop. 

so will run immediatly no matter what thread the async signal was
delivered to.

the same solution will work in cooperative implementations, but are
subject to normal scheduling latency issues.


= minimal proposal =

I think a good minimal solution will be the following, it neatly avoids
turning signals into exceptions, which may be problematic, but provides
for the common cases of signal usages while being compatible with both
cooperative and SMP systems.

== catching signals ==

implementations provide a way of catching signals such that the handler
runs as if in its own thread. something like the following

data SigInfo = ...
data HandlerType = SigOneShot | SigReset | SigIdempotent 

data SigAction = SigAction {
signalType :: HandlerType,
signalAction :: SigInfo - IO ()
}  | SigDefault | SigIgnore | SigExit (SigInfo - ExitStatus)

installHandler :: Signal - SigAction - IO SigAction
installHandler = ...

the action runs in its own thread.

SigExit is special in that it is equivalent to a 'signalAction' that
just calls exit, but since you know the program is going to exit, the
implementation can jump to the exit handler immediatly aborting the
current computation in whatever state it is in since it knows it will
never return to it.

SigIdempotent is the same as SigReset except multiple signals are
condensed into one with the SigInfo being chosen non-deterministically
from all those available.

== on exit ==

implementations also provide an onExit functionality, for registering
handlers that can be run when the program exits, as this is the most
common use of signals as exceptions, to clean up after oneself.

-- | temporarily register an exit handler for the duration of the action 
argument

Re: asynchronous exceptions

2006-04-06 Thread Marcin 'Qrczak' Kowalczyk
Simon Marlow [EMAIL PROTECTED] writes:

 I think it's unnecessary to treat signals in the way you do - you're
 assuming that a signal interrupts the current thread and runs a new
 computation (the signal handler) on the same stack, completely blocking
 the interrupted thread until the signal handler completes.  This is the
 wrong way to view signal handlers, IMO: they should run in completely
 separate threads (perhaps a higher priority thread, if possible).

This can be emulated in my model: by designating a thread for system
signals, possibly even letting it spawn a new thread for each signal.

Most Unix signals are supposed to abort the process however, and thus
a mechanism for aborting one thread from another is needed anyway.
I think async exceptions are not that much easier than
async signals.

Async signals include the ability to pause threads in safe points,
which is needed for SIGSTOP / SIGTSTP and for my fork() wrapper. This
is not archievable with signals spawning threads + async exceptions.

   + you don't have to block signals just because you happen to
 be holding a mutex.  Synchronisation with a signal handler
 is just synchronisation with another thread.

It's still very probable that taking a mutex coincides with the need
to block async exceptions: an async exception in the middle of a
critical section implies a danger of leaving data in an inconsistent
state. Reasons for automatic blocking of async signals carry over to
async exceptions.

 I agree with your assessment of the problems with interruptible
 operations in GHC: that it is impossible to completely block async
 exceptions across a computation.  We could certainly add a way to
 do this.  Is that the substance of your objection to GHC's async
 exception mechanism?

Regarding interruptible operations, this and one more thing that I
haven't written there:

The fact that some function uses an interruptible operation internally
is a visible aspect of its behavior, both in GHC design and in mine.
This means that choosing which operations are interruptible should be
done carefully: even if some operation blocks the thread, it might be
a bad choice for an interruption point, because usage of some blocking
operations should better not have to be exposed. In my case such
blocking but uninterruptible operations include waiting for a mutex,
and waiting for a lazy variable, among others.

But Concurrent Haskell uses a single construct of MVars as mutexes,
semaphores, or communication channels. The runtime can't recognize the
pattern of usage to distinguish these cases.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: asynchronous exceptions (was: RE: Concurrency)

2006-04-05 Thread David Roundy
On Tue, Apr 04, 2006 at 01:33:39PM +0100, Simon Marlow wrote:
 I'm not sure whether asynchronous exceptions should be in Haskell'.  I
 don't feel entirely comfortable about the interruptible operations
 facet of the design, and I'm hoping that STM can clean things up: after
 all, STM already gives you a much nicer way to program in an
 exception-safe way, as long as you aren't doing any real I/O.

For me, asynchronous exceptions are the primary reason to use concurrent
Haskell.  They're the only way I'm aware of to write a program that handles
signals in Haskell, and it's be a real shame to leave Haskell' programs
unable to handle signals--it means that any real-world programs that deal
with locking or the like will need to use non-standard extensions.  Unless
you can come up with some other way to deal with signals.  Having no chance
to clean up when control-C is hit isn't an acceptable alternative, and
neither is simply ignoring control-C and forcing users to run kill (and
then once again get no chance to clean up!).

Another option would be to hard-code signals into some sort of ordinary
exceptions, but that's not very good, since you'd then still want to split
exceptions into two camps, so that you could run a catch that only catches
signals generated *by* the IO action that you're running (i.e. you often
want to remove a file, and ignore any sort of failure, but don't want to
accidentally ignore a sigTERM that arrives during this process).  I suppose
you could do this with the complicated catchJust, but that's a pain.  It's
nice having a small (and documented) set of exceptions that most IO
operations can throw.

 The fact that throwTo can interrupt a takeMVar, but can't interrupt a
 foreign call, even a concurrent one, is a bit strange.  We have this odd
 situation in GHC right now where throwTo can interrupt threadDelay on
 Unix, but not on Windows because threadDelay maps directly to a foreign
 call to Sleep() on Windows.  To fix this I have to implement the I/O
 manager thread on Windows (I should do this anyway, though).
[...]
 The only guarantee you can give is the exception isn't delayed
 indefinitely, unless the target thread remains inside a block.  Just
 like the fairness property for MVars.

I think this is fine.  There's no need for strong guarantees that
asynchronous exceptions are delivered soon or interrrupt any particular
external function calls, or even interrupt particular standard library
functions.  At least to me, that's what makes them asynchronous.  In other
words, I wouldn't mind cooperative asynchronous function calls.  Which is
to say, that I don't see any reason the standard IO library shouldn't be
allowed (by the standard) to use block in all its calls.

This does limit the power of their application to signal-handling, but if
you really want signal-catching in ffi functions, those functions could
install their own signal-catchers.  My main concern is that as far as I can
see, without asynchronous exceptions there's no way to implement this sort
of functionality in pure Haskell.

Actually, I suppose you could do this with a (cooperative) implementation
of asynchronous exceptions using just MVars and concurrency by rewriting
all the IO calls you use to first check whether an asynchronous exception
has been thrown, but rewriting all the std library functions seems like a
rather crude way of doing this.  On the other hand, I suppose that this
could also provide a reference implementation of asynchronous exceptions
for any Haskell' that supports concurrency...
-- 
David Roundy
http://www.darcs.net
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: asynchronous exceptions (was: RE: Concurrency)

2006-04-05 Thread Simon Marlow
On 05 April 2006 12:47, David Roundy wrote:

 On Tue, Apr 04, 2006 at 01:33:39PM +0100, Simon Marlow wrote:
 The fact that throwTo can interrupt a takeMVar, but can't interrupt a
 foreign call, even a concurrent one, is a bit strange.  We have this
 odd situation in GHC right now where throwTo can interrupt
 threadDelay on Unix, but not on Windows because threadDelay maps
 directly to a foreign call to Sleep() on Windows.  To fix this I
 have to implement the I/O manager thread on Windows (I should do
 this anyway, though). [...] 
 The only guarantee you can give is the exception isn't delayed
 indefinitely, unless the target thread remains inside a block.  Just
 like the fairness property for MVars.
 
 I think this is fine.  There's no need for strong guarantees that
 asynchronous exceptions are delivered soon or interrrupt any
 particular external function calls, or even interrupt particular
 standard library functions.  At least to me, that's what makes them
 asynchronous.  In other words, I wouldn't mind cooperative
 asynchronous function calls.  Which is to say, that I don't see any
 reason the standard IO library shouldn't be allowed (by the standard)
 to use block in all its calls. 

Yes, maybe it's ok.  The nice thing about the way block works right now
is that it doesn't quite block all asynchronous exceptions, it actually
turns them into synchronous exceptions which are much more tractable.  

For example, in GHC's IO library I couldn't face the prospect of
scrutinising every line of code for exception-safety, so I just put a
block around everything that modifies Handle state.  This isn't nearly
as bad as it sounds, because any operation that blocks inside an I/O
operation is still interruptible, but because we know which operations
those are, we can be prepared to handle the exceptions.  In fact, since
the operations that block are mostly the I/O operations themselves,
we're already well prepared for handling exceptions there anyway.  So it
all works out nicely.

Concurrency abstractions built from MVars suffer a bit from
async-exception-safety.  The right way is to build these abstractions
using the exception-safe withMVar  modifyMVar family, but they impose
an overhead.  Fortunately STM is exactly the right solution here.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: asynchronous exceptions (was: RE: Concurrency)

2006-04-05 Thread Simon Marlow
On 05 April 2006 13:38, John Meacham wrote:

 On Wed, Apr 05, 2006 at 07:47:08AM -0400, David Roundy wrote:
 For me, asynchronous exceptions are the primary reason to use
 concurrent Haskell.  They're the only way I'm aware of to write a
 program that handles signals in Haskell, and it's be a real shame to
 leave Haskell' programs unable to handle signals--it means that any
 real-world programs that deal with locking or the like will need to
 use non-standard extensions.  Unless you can come up with some other
 way to deal with signals.  Having no chance to clean up when
 control-C is hit isn't an acceptable alternative, and neither is
 simply ignoring control-C and forcing users to run kill (and then
 once again get no chance to clean up!). 
 
 I have been giving signals some thought, and resarching what other
 languages do, and have a semi-proposal-maybe.

We should be careful here: the Haskell standard has so far remained
platform-independent, and I think it would be nice to keep it that way.


I'm not proposing that we ignore signals, just that we should clearly
delimit the platform-specific bits, perhaps by putting signal support
into an addendum.

 signals tend to be used for one of a couple purposes (some can fall
 into multiple categories):
 
 signal a synchronous exceptional event - SIGFPE, SIGPIPE, SIGILL,
 SIGSEGV 
 signal an asynchronous exceptional event - SIGINT, SIGHUP
 (interactive) 
 inform the app of an event it might want to take note of -  SIGALRM,
 SIGCHLD, SIGWINCH, SIGHUP (daemon) 
 
 I think it would make sense to have 3 mechanisms to cover these cases.
 
 signal a synchronous exceptional event
 - raise a (possibly imprecise) exception on the thread that produced
 the signal. 

GHC has no support for these right now.  They're pretty tricky to
handle, because the OS thread that caused the signal to be raised is
stopped at some arbitrary instruction, and it would require some serious
acrobatics to munge that OS thread into a state where it is possible to
raise the (Haskell) exception.  I do vaguely recall that people have
achieved this in the past, in order to use page faults for write
barriers, that sort of thing.

SIGPIPE is possibly easier than the others.  SIGFPE you can usually turn
off in favour of exceptional values instead.

 signal an asynchronous exceptional event
 - the user should be able to choose the threads on which they wish to
   catch these, those that need to clean up after themselves.
 
 inform the app of an event it might want to take note of
 - these should run on their own thread, concurrently to all other
   threads

GHC directly support the latter version, and you can implement the
former with a little extra code and a global variable.  I think it would
be nice to do as you suggest and provide a way to have the async signals
turn directly into exceptions.

One problem, though, is that because we can't interrupt a foreign call
with an async exception, ^C can be rather unresponsive.  Perhaps I
should look into this and see whether it would be possible in GHC for a
concurrent foreign call to be interruptible; it would involve
terminating the foreign call somehow (pthread_cancel?) before raising
the exception.  We can't do this in a bound thread, however.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: asynchronous exceptions

2006-04-05 Thread Marcin 'Qrczak' Kowalczyk
Simon Marlow [EMAIL PROTECTED] writes:

 I'm not sure whether asynchronous exceptions should be in Haskell'.
 I don't feel entirely comfortable about the interruptible operations
 facet of the design,

I designed that differently for my language. There is a distinct
synchronous mode where asynchronous exceptions are handled by
certain operations only, similarly to POSIX deferred mode of thread
cancellation. This allows to use blocking operations without being
interrupted.

http://www.cs.ioc.ee/tfp-icfp-gpce05/tfp-proc/06num.pdf

Actually I support asynchronous signals, not just exceptions:
the reaction to a signal can be something other than throwing an
exception. For example Linux SIGWINCH should be handled by resizing
and repainting the screen at an appropriate moment, not by aborting
any computation in progress.

 The fact that throwTo can interrupt a takeMVar, but can't interrupt
 a foreign call, even a concurrent one, is a bit strange.

When entering foreign mode in C code embedded in Kogut (which
corresponds to concurrent foreign imports in Haskell but is less
convenient to use), it's possible to specify how that thread wishes
to be interrupted in case someone else sends it an asynchronous signal
during the foreign trip.

The only implemented application of this mechanism is sending a Unix
signal. This is enough to interrupt blocking syscalls like waitpid.
If waitpid fails and errno == EINTR, pending signals for this thread
are processed and waiting continues (unless some signal handler has
thrown an exception).

Implementing this without race conditions requires a sigsafe library
or something equivalent.


John Meacham [EMAIL PROTECTED] writes:

  * do we require the thrower to 'block' until the signal is recieved?
   (only relevant to pre-emptive implementations)

My language doesn't do it, and I'm not convinced that Haskell should
block. It's more efficient to make this non-blocking, and I think
usually this is what is needed.

  * what happens if mutilple thrown exceptions pile up before the
catcher gets to them?

In my language each thread has a queue of pending asynchronous
signals, and they are processed in order.

Handling an asynchronous signal, or throwing an exception until it is
handled, blocks further signals automatically, so more signals are
processed only after the previous signal was handled.

An exception handler is not in a tail position wrt. the catching
construct, for two reasons: the state of asynchronous signals is
restored after handling the exception, and a stack trace shown when
the exception is propagated to the toplevel without being handled
includes code in unfinished exception handlers.

There is a separate exception handling syntax when the exception
should be considered already handled, for cases when the exception
handler should be in a tail context.

  * what happns to exceptions that fall off the end of threads, or the
main thread? (should be answered anyway)

In my case a thread body ends with a value or with an exception,
and this can be examined when joining a thread, or by default the
exception is propagated in the joiner. This has a disadvantage
that errors in threads nobody waits for might be left undetected,
unless they use an explicit wrapper.

For the main thread there is a settable handler of exceptions
reaching the toplevel, which by default handles some exceptions
specially (Unix signals, and a request of program termination),
and others are printed along with a stack trace.

  * promtness? how much work is the target allowed to do before it sees
the exception? pthreads allows an implementation to delay processing
an exception to a cancellation point do we want the same thing in
haskell?

Perhaps. My design includes that.


David Roundy [EMAIL PROTECTED] writes:

 It would also be nice to address signal behavior, and by default state that
 signals should be converted to asynchronous exceptions.

This is not enough for SIGWINCH, or for SIGHUP used to trigger
reloading configuration files.

OTOH purity of Haskell's functional subsystem has some nice
consequences for asynchronous exceptions which don't have to carry
over to asynchronous signals which don't necessarily abort the
computation. If the signal is guaranteed to abort some part of
IO code, then it makes sense to revert thunks under evaluation.
If the signal only causes to execute some handler, then reverting
them might be wasteful, as they will soon be needed again.

 The only downside I can see of this as default behavior would be
 that in cooperative systems the response to a sigTERM might be
 very slow.

Right, it's a pity, and I agree that benefits outweigh this problem.

In my implementation the thread which handles system signals
(settable, defaults to the main thread) needs to be chosen by the
scheduler in order to process the signal. It might take some time
if there is a lot of threads.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^