[Haskell-cafe] ANN: asynchronous-exceptions

Michael Snoyman michael at snoyman.com
Wed Feb 5 15:55:10 UTC 2014


So you're saying that it's expected behavior for the shim library you're
providing to have drastically different behavior between different versions
of GHC? I don't think that's a good idea at all.

In any event, this approach is still predicated on the idea that you can
identify an asynchronous event from its type. There are multiple problems
with this:

* As demonstrated with my previous example, not all asynchronous exceptions
identify themselves as such.
* There is no requirement that only asynchronous-type exceptions be thrown
asynchronously. throwTo works with any instance of Exception.
* 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.

To demonstrate that last point, consider the example code below, which uses
your asynchronous type machinery and the async package. The usage of
`trySync` in `main` *should* catch that exception, since it is no longer
asynchronous, but a type-only approach cannot handle that situation.
ClassyPrelude's tryAny, on the other hand, gives the correct output.

{-# LANGUAGE DeriveDataTypeable #-}
import Control.Exception.Async
import Control.Concurrent.Async
import Control.Concurrent
import Control.Exception
import Data.Unique
import Data.Typeable

data Timeout = Timeout
    deriving (Typeable, Eq)
instance Show Timeout where
    show _ = "Async Timeout"
instance Exception Timeout where
    fromException = asyncExceptionFromException
    toException = asyncExceptionToException

asyncTimeout n f = do
    pid <- myThreadId
    killer <- forkIO $ do
        threadDelay n
        throwTo pid Timeout
    res <- f
    killThread pid
    return res

main :: IO ()
main = do
    res <- trySync f
    print res

f :: IO String
f = do
    x <- async $ asyncTimeout 1000000 $ do
        threadDelay 2000000
        return "Finished"
    wait x



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

> It works as expected.
>
> With GHC 7.8 it doesn't print the timeout exception.
>
> With earlier GHC it does (again, as expected, because the timeout
> exception isn't marked as asynchronous). In practice one should rarely
> want to use System.Timeout anyway (because of the overflow issue), and
> I'm going to patch one of the better timeout packages (such as
> unbounded-delays) to support asynchronous-exceptions.
>
> * Michael Snoyman <michael at snoyman.com> [2014-02-05 16:56:31+0200]
> > I don't think this package works as expected. Consider the following:
> >
> > import           Control.Concurrent
> > import           Control.Exception.Async
> > import           System.Timeout
> >
> > main :: IO ()
> > main = do
> >     timeout 1000000 $ do
> >         threadDelay 10000000 `catchSync` \e -> do
> >             print e
> >             threadDelay 10000000
> >     return ()
> >
> > The expected behavior would be that the timeout- an async exception-
> would
> > kill the thread delay, the catch would ignore the async exception, and
> the
> > program would exit. In reality, catchSync treats the timeout as a
> > synchronous exception, prints it, and delays once again. Compare this to
> > classy-prelude's catchAny, which handles the situation correctly, via the
> > technique I described in "Catching all exceptions."[1]
> >
> > In this case, the issue is that the timeout exception type is not
> > recognized as async, and a special case could be added to handle that
> > exception type[2]. However, I think the overall approach of determining
> > *how* an exception was thrown based on *what* was thrown is not tenable.
> >
> > [1]
> >
> https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions
> > [2] It's a bit difficult to do so, since IIRC the type is never exported.
> > But a hack using the Typeable instance- while ugly- is likely possible.
> >
> >
> > On Wed, Feb 5, 2014 at 1:28 PM, Roman Cheplyaka <roma at ro-che.info>
> wrote:
> >
> > > The links are:
> > >
> > > http://hackage.haskell.org/package/asynchronous-exceptions
> > > https://github.com/feuerbach/asynchronous-exceptions
> > >
> > > * Roman Cheplyaka <roma at ro-che.info> [2014-02-05 13:23:38+0200]
> > > > It is often useful to distinguish between synchronous and
> asynchronous
> > > > exceptions. The common idiom is to run a user-supplied computation
> > > > catching any synchronous exceptions but allowing asynchronous
> exceptions
> > > > (such as user interrupt) pass through.
> > > >
> > > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type
> that
> > > > solves this problem.
> > > >
> > > > asynchronous-exceptions is a new package that serves two purposes:
> > > > * provide compatibility with older `base` versions that lack the
> > > >   `SomeAsyncException` type
> > > > * define convenient functions for catching only synchronous
> exceptions
> > > >
> > > > Roman
> > >
> > > _______________________________________________
> > > Haskell-Cafe mailing list
> > > Haskell-Cafe at haskell.org
> > > http://www.haskell.org/mailman/listinfo/haskell-cafe
> > >
> > >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140205/13f6a2b9/attachment.html>


More information about the Haskell-Cafe mailing list