[Haskell-cafe] ANN: asynchronous-exceptions

Michael Snoyman michael at snoyman.com
Wed Feb 5 16:48:22 UTC 2014


On Wed, Feb 5, 2014 at 6:28 PM, Roman Cheplyaka <roma at ro-che.info> wrote:

> * Michael Snoyman <michael at snoyman.com> [2014-02-05 17:55:10+0200]
> > * If an asynchronous-type exception is caught and then rethrown as a
> > synchronous exception, the type-based approach will still treat it as
> > asynchronous, though it should be recognized as synchronous at that
> point.
>
> I say it shouldn't. I usually don't care by what means an exception was
> thrown. I care that exceptions that are meant to be thrown
> asynchronously (that is: they do not originate from the currently
> executing code in the current thread, but are some indication of an
> outside event) are not treated the same as exceptions that arise from
> the code in the current thread.
>
> Example:
>
>   {-# LANGUAGE ScopedTypeVariables #-}
>   import System.Timeout
>   import Control.Concurrent
>   import Control.Exception
>   import Control.Exception.Async
>
>   main = do
>     timeout (10^5) $
>       (threadDelay (10^6) `catch` (\(_ :: IOException) -> print 1))
>         `catchSync` (\_ -> print 2)
>
> I don't expect any of the exception handlers here to fire because
> threadDelay doesn't throw any exceptions. This is my intention. The fact
>

And just to point out yet again: the second exception handler *does* fire
in GHC 7.6 and earlier.


> that, as Edsko points out, exception are re-thrown synchronously, is a
> subtle technicality and I don't want to care about it. Remember that
>
>   threadDelay (10^6) `catch` (\(_ :: IOException) -> print 1)
>
> sits somewhere deep inside a user-supplied action. Thus, the semantics
> of my clear-intentioned code
>
>   timeout (10^5) $ userAction `catchSync` (\_ -> print 2)
>
> in the approach you advocate would depend on whether, somewhere deep
> inside a library used by the user action, any exceptions are caught.
> This is not compositional nor useful.
>
> Roman
>

I can't think of any situation in which the semantics you're implying make
sense. To me, catching synchronous exception is a simple concept: if an
exception is generated internally to `userAction`, then it's a synchronous
exception. If it was terminated by something external, then it's
asynchronous. I'm not sure what you're getting at about my approach
requiring knowledge of what's going on deep inside a library.

The real question which is not explained in your package is what use case
you're actually trying to address. Here's a prime example I've run into:
you're writing a web application which uses a third-party library. If that
library throws an exception of any type, you want to catch the exception
and display an appropriate error message (or perhaps return some data from
another source). However, we still want the web application to respect
timeout messages from the server to avoid slowloris attacks. The handler
code would look like:

myHandler = do
    eres <- tryAnyDeep someLibraryFunction
    case eres of
        Left e -> tellUser "I'm sorry, there was an issue making the query"
        Right x -> displayData x

The goal is that, under no circumstances, should someLibraryFunction be
able to case the exception to escape tryAnyDeep. This includes rethrowing
some async exception that it received from, e.g., a timeout. This would not
be honored by trySync.

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140205/4b834249/attachment.html>


More information about the Haskell-Cafe mailing list