
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

The links are:
http://hackage.haskell.org/package/asynchronous-exceptions
https://github.com/feuerbach/asynchronous-exceptions
* Roman Cheplyaka
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

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...
[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
The links are:
http://hackage.haskell.org/package/asynchronous-exceptions https://github.com/feuerbach/asynchronous-exceptions
* Roman Cheplyaka
[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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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... [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
wrote: The links are:
http://hackage.haskell.org/package/asynchronous-exceptions https://github.com/feuerbach/asynchronous-exceptions
* Roman Cheplyaka
[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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Roman,
One other question: in Michael's article, he also mentions the possibility of:
"Consider that, for some strange reason, we decided to asynchronously
throw an IOException to a worker thread"
Meaning that you can throwTo any exception asynchronouly, even if it
is not a SomeAsyncException. At least from what I gathered from (GHC
Head) throwTo code, this does not seem to be a restriction.
Thus, your module will work for any well behaved code that does the
right thing, and respects the SomeAsyncException superclass, but not
for other spurious asynchronous exceptions, right?
I'm just trying to frame the possible use cases of your library.
Thanks
Joao
2014-02-05 Roman Cheplyaka
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
[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... [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
wrote: The links are:
http://hackage.haskell.org/package/asynchronous-exceptions https://github.com/feuerbach/asynchronous-exceptions
* Roman Cheplyaka
[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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi João,
* João Cristóvão
Hi Roman,
One other question: in Michael's article, he also mentions the possibility of: "Consider that, for some strange reason, we decided to asynchronously throw an IOException to a worker thread"
Meaning that you can throwTo any exception asynchronouly, even if it is not a SomeAsyncException. At least from what I gathered from (GHC Head) throwTo code, this does not seem to be a restriction.
Thus, your module will work for any well behaved code that does the right thing, and respects the SomeAsyncException superclass, but not for other spurious asynchronous exceptions, right?
Precisely.
I'm just trying to frame the possible use cases of your library. Thanks Joao
2014-02-05 Roman Cheplyaka
: 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
[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... [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
wrote: The links are:
http://hackage.haskell.org/package/asynchronous-exceptions https://github.com/feuerbach/asynchronous-exceptions
* Roman Cheplyaka
[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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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.
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
* Michael Snoyman
[2014-02-05 16:56:31+0200] 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]
[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
wrote: The links are:
http://hackage.haskell.org/package/asynchronous-exceptions https://github.com/feuerbach/asynchronous-exceptions
* Roman Cheplyaka
[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
https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching... 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

* Michael Snoyman
* 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 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

On Wed, Feb 5, 2014 at 6:28 PM, Roman Cheplyaka
* 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
* Michael Snoyman
[2014-02-05 17:55:10+0200] 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

Hi! Please let me add two cents to your discussion. Just for your information. There is a working approach, when the exceptions can be indeed successfully caught within the asynchronous computation. Moreover, there is also the working try-finally block, which is more difficult to implement. This is the async workflow in F# and their Async<’T> type is actually a monad. Only they use the continuations, namely three continuations: (1) the main branch; (2) the branch for catching exceptions; (3) the branch for immediate canceling the computation. They have no special «asynchronous» exceptions that would differ from synchronous ones. By the way, I have implemented a similar approach in my library aivika available on hackage (module Simulation.Aivika.Internal.Cont). I can catch the IO exceptions as well as I can process so called the finally blocks, and my own tests show that it works in Haskell. Thanks, David

Ok, this clears things up. I misinterpreted your approach thinking that
you're also solving the problem of distinguishing async vs sync
exceptions, only based on how they were thrown instead of their type.
I now see that it isn't the case — you're catching *all* exceptions.
(And run the timeout handler in a different thread.)
So no wonder that asynchronous-exceptions (whose description says that
it lets differentiate between sync and async exceptions, in a certain
sense) doesn't help you — you simply don't want any exceptions at all.
My use case is simpler — I write testing libraries. If a test throws an
exception, we have to decide whether we want to report it as a test's
failure or it's a bigger problem and we want to wrap up.
I don't think there's a universally right way to make this decision. It
depends on what exceptions exist and what threads they can be thrown to.
E.g. if there existed something like UserInterrupt but which could be
thrown to any active thread, not only the main thread, then the approach
"run in a separate thread and log any exceptions from that thread"
simply wouldn't work.
For tasty, based on the async exceptions I'm aware of, I think your
approach is overall better. It's almost as simple, doesn't require
patching 3rd-party timeout libraries, and catches StackOverflow (which
is desirable). So I'll switch to it instead.
For smallcheck, the overhead of forkIO might be significant, because it
has to be performed for every single property check, and those can be
numerous and very quick. I put together a simple benchmark
(http://lpaste.net/99532 if anyone is interested) which shows that
overhead can be noticable (16% for async vs 4% for simple catch) but
tolerable, and it will be even less for more realistic properties.
So I'll probably use the async approach there, too, although I may
reconsider that in the future if I ever get to optimizing smallcheck and
squeezing out those percents.
As for the package itself, let's see if others will find any good use
cases for it. I'll update the docs with some conclusions from this
thread.
And thanks for your input.
Roman
* Michael Snoyman
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

Roman,
By mere chance today I was, about the same time you published your
library, working on the suggestion made by Michael in the end of his
original blog post: splitting the async exceptions part from
classy-prelude (he is ok with this).
https://github.com/jcristovao/async-exception
I was not yet sure about the namespace, I had opted for:
Control.Concurrent.Async.Exception
But yours makes more sense,
Control.Async.Exception
I agree that the two solutions address different problems, and as you
say, for controlled situations where performance is critical yours
indeed adds less overhead. But for more general solutions, Michael's
solution - split from Classy prelude, seems to be the way to go, and
thus my 'split' makes sense if you don't need the remaining classy
prelude.
As such, I was considering the namespace:
Control.Async.Exception.All
To differentiate from yours, signaling that it handles _all_ exceptions.
What do you think?
Anyhow, I also think Joachim suggestion (of at least implementing the
new exception classes in base-compat) makes sense, so I volunteer to
add to the work I already done here:
https://github.com/sol/base-compat/pull/2
(If the patch gets accepted, of course).
Cheers,
João
2014-02-05 Roman Cheplyaka
Ok, this clears things up. I misinterpreted your approach thinking that you're also solving the problem of distinguishing async vs sync exceptions, only based on how they were thrown instead of their type.
I now see that it isn't the case -- you're catching *all* exceptions. (And run the timeout handler in a different thread.)
So no wonder that asynchronous-exceptions (whose description says that it lets differentiate between sync and async exceptions, in a certain sense) doesn't help you -- you simply don't want any exceptions at all.
My use case is simpler -- I write testing libraries. If a test throws an exception, we have to decide whether we want to report it as a test's failure or it's a bigger problem and we want to wrap up.
I don't think there's a universally right way to make this decision. It depends on what exceptions exist and what threads they can be thrown to. E.g. if there existed something like UserInterrupt but which could be thrown to any active thread, not only the main thread, then the approach "run in a separate thread and log any exceptions from that thread" simply wouldn't work.
For tasty, based on the async exceptions I'm aware of, I think your approach is overall better. It's almost as simple, doesn't require patching 3rd-party timeout libraries, and catches StackOverflow (which is desirable). So I'll switch to it instead.
For smallcheck, the overhead of forkIO might be significant, because it has to be performed for every single property check, and those can be numerous and very quick. I put together a simple benchmark (http://lpaste.net/99532 if anyone is interested) which shows that overhead can be noticable (16% for async vs 4% for simple catch) but tolerable, and it will be even less for more realistic properties. So I'll probably use the async approach there, too, although I may reconsider that in the future if I ever get to optimizing smallcheck and squeezing out those percents.
As for the package itself, let's see if others will find any good use cases for it. I'll update the docs with some conclusions from this thread.
And thanks for your input.
Roman
* Michael Snoyman
[2014-02-05 18:48:22+0200] 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Well, since you happened to ask me (although I am as good a bikeshedder
as the next person), I think that you don't need to mention Async
anywhere in the module name, since the module doesn't make any attempt
to differentiate between sync and async exceptions.
And the fact that the module uses the 'async' library is just an
implementation detail.
I'd go with something like Control.Exception.CatchAny.
Roman
* João Cristóvão
Roman,
By mere chance today I was, about the same time you published your library, working on the suggestion made by Michael in the end of his original blog post: splitting the async exceptions part from classy-prelude (he is ok with this).
https://github.com/jcristovao/async-exception
I was not yet sure about the namespace, I had opted for: Control.Concurrent.Async.Exception
But yours makes more sense, Control.Async.Exception
I agree that the two solutions address different problems, and as you say, for controlled situations where performance is critical yours indeed adds less overhead. But for more general solutions, Michael's solution - split from Classy prelude, seems to be the way to go, and thus my 'split' makes sense if you don't need the remaining classy prelude.
As such, I was considering the namespace: Control.Async.Exception.All
To differentiate from yours, signaling that it handles _all_ exceptions. What do you think?
Anyhow, I also think Joachim suggestion (of at least implementing the new exception classes in base-compat) makes sense, so I volunteer to add to the work I already done here: https://github.com/sol/base-compat/pull/2
(If the patch gets accepted, of course).
Cheers, João
2014-02-05 Roman Cheplyaka
: Ok, this clears things up. I misinterpreted your approach thinking that you're also solving the problem of distinguishing async vs sync exceptions, only based on how they were thrown instead of their type.
I now see that it isn't the case -- you're catching *all* exceptions. (And run the timeout handler in a different thread.)
So no wonder that asynchronous-exceptions (whose description says that it lets differentiate between sync and async exceptions, in a certain sense) doesn't help you -- you simply don't want any exceptions at all.
My use case is simpler -- I write testing libraries. If a test throws an exception, we have to decide whether we want to report it as a test's failure or it's a bigger problem and we want to wrap up.
I don't think there's a universally right way to make this decision. It depends on what exceptions exist and what threads they can be thrown to. E.g. if there existed something like UserInterrupt but which could be thrown to any active thread, not only the main thread, then the approach "run in a separate thread and log any exceptions from that thread" simply wouldn't work.
For tasty, based on the async exceptions I'm aware of, I think your approach is overall better. It's almost as simple, doesn't require patching 3rd-party timeout libraries, and catches StackOverflow (which is desirable). So I'll switch to it instead.
For smallcheck, the overhead of forkIO might be significant, because it has to be performed for every single property check, and those can be numerous and very quick. I put together a simple benchmark (http://lpaste.net/99532 if anyone is interested) which shows that overhead can be noticable (16% for async vs 4% for simple catch) but tolerable, and it will be even less for more realistic properties. So I'll probably use the async approach there, too, although I may reconsider that in the future if I ever get to optimizing smallcheck and squeezing out those percents.
As for the package itself, let's see if others will find any good use cases for it. I'll update the docs with some conclusions from this thread.
And thanks for your input.
Roman
* Michael Snoyman
[2014-02-05 18:48:22+0200] 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi again,
since the module doesn't make any attempt to differentiate between sync and async exceptions.
Well... If I am understanding this correctly, and I might not be:
Michael code efectively distinguishes exceptions thrown asynchronously
with throwTo from synchronous exceptions generated inside the
catchAny. Since the code run by catchAny is run in a separate
'anonymous' thread created by withAsync, there's no way you can throw
it an asynchronous exception (ThreadKilled) with throwTo - you don't
know its thread id.
Any code using throwTo will just know the calling thread, and thus
you've got a way to distinguish between received asynchronous
exceptions (the timeout example) and synchronous exceptions generated
inside the function your passing to catchAny.
Thus, in one hand I do not think "CatchAny" makes justice to the fact
that async exceptions received by the thread using catchAny are _not_
caught by catchAny.
In the other hand, I was just thinking: what if the computation runing
in catchAny in the anonymous thread generates a Ctrl-C, if, for
example, it interacts with stdin.
However, Control.Exception states that:
"UserInterrupt: This exception is raised by default in the __main__
thread of the program when the user requests to terminate the program
via the usual mechanism(s) (e.g. Control-C in the console). "
(emphasis mine)
Thus, the problem does not pose it self. The remaining two
asynchronous exceptions (StackOverflow and HeapOverflow) are again a
result of the inner function execution, and could, from a certain
point of view, be considered synchronous.
So, for all intents and purposes, this catchAny and such _do_ allow to
distinguish between asynchronous exceptions (sent with throwTo) or
synchronous exceptions (generated as a result of the execution of the
computation passed to catchAny). Asynchronous exceptions do not occur
inside the CatchAny associated computation, except perhaps the
ThreadKilled signal forward by its calling thread/parent thread when
it self is killed - an in that particular case, it doesn't really
matter. That asynchronous exception would be caught by catchAny, but
the result returned by the exception handler would not be used - the
calling thread is also dying.
Am I getting this right?
João
2014-02-05 Roman Cheplyaka
Well, since you happened to ask me (although I am as good a bikeshedder as the next person), I think that you don't need to mention Async anywhere in the module name, since the module doesn't make any attempt to differentiate between sync and async exceptions.
And the fact that the module uses the 'async' library is just an implementation detail.
I'd go with something like Control.Exception.CatchAny.
Roman
* João Cristóvão
[2014-02-05 22:13:19+0000] Roman,
By mere chance today I was, about the same time you published your library, working on the suggestion made by Michael in the end of his original blog post: splitting the async exceptions part from classy-prelude (he is ok with this).
https://github.com/jcristovao/async-exception
I was not yet sure about the namespace, I had opted for: Control.Concurrent.Async.Exception
But yours makes more sense, Control.Async.Exception
I agree that the two solutions address different problems, and as you say, for controlled situations where performance is critical yours indeed adds less overhead. But for more general solutions, Michael's solution - split from Classy prelude, seems to be the way to go, and thus my 'split' makes sense if you don't need the remaining classy prelude.
As such, I was considering the namespace: Control.Async.Exception.All
To differentiate from yours, signaling that it handles _all_ exceptions. What do you think?
Anyhow, I also think Joachim suggestion (of at least implementing the new exception classes in base-compat) makes sense, so I volunteer to add to the work I already done here: https://github.com/sol/base-compat/pull/2
(If the patch gets accepted, of course).
Cheers, João
2014-02-05 Roman Cheplyaka
: Ok, this clears things up. I misinterpreted your approach thinking that you're also solving the problem of distinguishing async vs sync exceptions, only based on how they were thrown instead of their type.
I now see that it isn't the case -- you're catching *all* exceptions. (And run the timeout handler in a different thread.)
So no wonder that asynchronous-exceptions (whose description says that it lets differentiate between sync and async exceptions, in a certain sense) doesn't help you -- you simply don't want any exceptions at all.
My use case is simpler -- I write testing libraries. If a test throws an exception, we have to decide whether we want to report it as a test's failure or it's a bigger problem and we want to wrap up.
I don't think there's a universally right way to make this decision. It depends on what exceptions exist and what threads they can be thrown to. E.g. if there existed something like UserInterrupt but which could be thrown to any active thread, not only the main thread, then the approach "run in a separate thread and log any exceptions from that thread" simply wouldn't work.
For tasty, based on the async exceptions I'm aware of, I think your approach is overall better. It's almost as simple, doesn't require patching 3rd-party timeout libraries, and catches StackOverflow (which is desirable). So I'll switch to it instead.
For smallcheck, the overhead of forkIO might be significant, because it has to be performed for every single property check, and those can be numerous and very quick. I put together a simple benchmark (http://lpaste.net/99532 if anyone is interested) which shows that overhead can be noticable (16% for async vs 4% for simple catch) but tolerable, and it will be even less for more realistic properties. So I'll probably use the async approach there, too, although I may reconsider that in the future if I ever get to optimizing smallcheck and squeezing out those percents.
As for the package itself, let's see if others will find any good use cases for it. I'll update the docs with some conclusions from this thread.
And thanks for your input.
Roman
* Michael Snoyman
[2014-02-05 18:48:22+0200] 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am I getting this right?
Not quite.
The enclosed computation may get asynchronous exceptions whatever
definition of 'asynchronous' you use — the exact one (by throw method)
or the approximate one (by type).
Just a couple of examples:
* The thread may catch an async exception from the RTS (such as
BlockedIndefinitelyOnMVar or StackOverflow)
* The thread may spawn other threads, passing its pid to them, and one
of its children may eventually kill it
So I'd say this method allows to catch any exceptions "related" to
the computation, synchronous or asynchronous. It is this "relatedness"
that is enforced by running it in a separate thread.
Roman
* João Cristóvão
Hi again,
since the module doesn't make any attempt to differentiate between sync and async exceptions.
Well... If I am understanding this correctly, and I might not be: Michael code efectively distinguishes exceptions thrown asynchronously with throwTo from synchronous exceptions generated inside the catchAny. Since the code run by catchAny is run in a separate 'anonymous' thread created by withAsync, there's no way you can throw it an asynchronous exception (ThreadKilled) with throwTo - you don't know its thread id.
Any code using throwTo will just know the calling thread, and thus you've got a way to distinguish between received asynchronous exceptions (the timeout example) and synchronous exceptions generated inside the function your passing to catchAny.
Thus, in one hand I do not think "CatchAny" makes justice to the fact that async exceptions received by the thread using catchAny are _not_ caught by catchAny.
In the other hand, I was just thinking: what if the computation runing in catchAny in the anonymous thread generates a Ctrl-C, if, for example, it interacts with stdin. However, Control.Exception states that: "UserInterrupt: This exception is raised by default in the __main__ thread of the program when the user requests to terminate the program via the usual mechanism(s) (e.g. Control-C in the console). " (emphasis mine)
Thus, the problem does not pose it self. The remaining two asynchronous exceptions (StackOverflow and HeapOverflow) are again a result of the inner function execution, and could, from a certain point of view, be considered synchronous.
So, for all intents and purposes, this catchAny and such _do_ allow to distinguish between asynchronous exceptions (sent with throwTo) or synchronous exceptions (generated as a result of the execution of the computation passed to catchAny). Asynchronous exceptions do not occur inside the CatchAny associated computation, except perhaps the ThreadKilled signal forward by its calling thread/parent thread when it self is killed - an in that particular case, it doesn't really matter. That asynchronous exception would be caught by catchAny, but the result returned by the exception handler would not be used - the calling thread is also dying.
Am I getting this right? João
2014-02-05 Roman Cheplyaka
: Well, since you happened to ask me (although I am as good a bikeshedder as the next person), I think that you don't need to mention Async anywhere in the module name, since the module doesn't make any attempt to differentiate between sync and async exceptions.
And the fact that the module uses the 'async' library is just an implementation detail.
I'd go with something like Control.Exception.CatchAny.
Roman
* João Cristóvão
[2014-02-05 22:13:19+0000] Roman,
By mere chance today I was, about the same time you published your library, working on the suggestion made by Michael in the end of his original blog post: splitting the async exceptions part from classy-prelude (he is ok with this).
https://github.com/jcristovao/async-exception
I was not yet sure about the namespace, I had opted for: Control.Concurrent.Async.Exception
But yours makes more sense, Control.Async.Exception
I agree that the two solutions address different problems, and as you say, for controlled situations where performance is critical yours indeed adds less overhead. But for more general solutions, Michael's solution - split from Classy prelude, seems to be the way to go, and thus my 'split' makes sense if you don't need the remaining classy prelude.
As such, I was considering the namespace: Control.Async.Exception.All
To differentiate from yours, signaling that it handles _all_ exceptions. What do you think?
Anyhow, I also think Joachim suggestion (of at least implementing the new exception classes in base-compat) makes sense, so I volunteer to add to the work I already done here: https://github.com/sol/base-compat/pull/2
(If the patch gets accepted, of course).
Cheers, João
2014-02-05 Roman Cheplyaka
: Ok, this clears things up. I misinterpreted your approach thinking that you're also solving the problem of distinguishing async vs sync exceptions, only based on how they were thrown instead of their type.
I now see that it isn't the case -- you're catching *all* exceptions. (And run the timeout handler in a different thread.)
So no wonder that asynchronous-exceptions (whose description says that it lets differentiate between sync and async exceptions, in a certain sense) doesn't help you -- you simply don't want any exceptions at all.
My use case is simpler -- I write testing libraries. If a test throws an exception, we have to decide whether we want to report it as a test's failure or it's a bigger problem and we want to wrap up.
I don't think there's a universally right way to make this decision. It depends on what exceptions exist and what threads they can be thrown to. E.g. if there existed something like UserInterrupt but which could be thrown to any active thread, not only the main thread, then the approach "run in a separate thread and log any exceptions from that thread" simply wouldn't work.
For tasty, based on the async exceptions I'm aware of, I think your approach is overall better. It's almost as simple, doesn't require patching 3rd-party timeout libraries, and catches StackOverflow (which is desirable). So I'll switch to it instead.
For smallcheck, the overhead of forkIO might be significant, because it has to be performed for every single property check, and those can be numerous and very quick. I put together a simple benchmark (http://lpaste.net/99532 if anyone is interested) which shows that overhead can be noticable (16% for async vs 4% for simple catch) but tolerable, and it will be even less for more realistic properties. So I'll probably use the async approach there, too, although I may reconsider that in the future if I ever get to optimizing smallcheck and squeezing out those percents.
As for the package itself, let's see if others will find any good use cases for it. I'll update the docs with some conclusions from this thread.
And thanks for your input.
Roman
* Michael Snoyman
[2014-02-05 18:48:22+0200] 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Feb 6, 2014 at 8:17 AM, Roman Cheplyaka
Am I getting this right?
Not quite.
The enclosed computation may get asynchronous exceptions whatever definition of 'asynchronous' you use -- the exact one (by throw method) or the approximate one (by type).
Just a couple of examples:
* The thread may catch an async exception from the RTS (such as BlockedIndefinitelyOnMVar or StackOverflow) * The thread may spawn other threads, passing its pid to them, and one of its children may eventually kill it
So I'd say this method allows to catch any exceptions "related" to the computation, synchronous or asynchronous. It is this "relatedness" that is enforced by running it in a separate thread.
Roman
I definitely think this is important to get our terminology right. A lot of the scariness of async exceptions likely spawns from the fact that we use the same term to refer to a number of very different cases. Let me give a crack at breaking down exceptions: * An exception with a synchronous type (e.g., IOException) thrown via throwIO. This is the most synchronous of synchronous exceptions. * An exception with an asynchronous type (e.g., UserInterrupt) thrown via throwIO. There's legitimate room for debate as to what we should call this. For my purposes, I'd want to call it a synchronous exception. * An exception with a synchronous type thrown via throwTo. Similar to previous bullet, but I'd consider this asynchronous. * An exception with an asynchronous type thrown via throwTo. This is solidly an asynchronous exception. Then we have some more interesting questions: * What *is* an asynchronous type? By including BlockedIndefinitelyOnMVar, it seems like you're defining it to include any exception generated by the RTS. However, I'd consider it a synchronous exception: it is generated in direct consequence of performing an IO action. It just happens to be generated by the RTS instead of via some library talking to the filesystem. * What happens if an async exception is caught and then rethrown? Has it transformed itself into a synchronous exception? That's a tricky question, and likely depends on the exact manner in which is was caught. * What happens if a function utilizes some form of asynchronous exception mechanism to affect its behavior? The prime example of this is `timeout`, or better, the `asyncTimeout` function I displayed above. Internally to that function, I think that's an async exception. However, for a *caller* of that function, the behavior is actually synchronous: there was no notification from the outside world changing the behavior of this function, it simply has the possibility to terminate by throwing a Timeout, the same way a function may terminate by throwing an IOException. That last bullet is crucial to the question of whether classy-prelude's and João's catching functions are asynchronous or not. But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do. Michael

Thanks Roman and Michael for the latest clarifications: I had indeed forgot the case where a thread runned in catchAny spawn child threads that kill their parent.
But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do.
The word currently in my head is 'inner', although Roman's suggestion
of 'enclosed' looks fine too. Internal is also correct, but as it is
regularly used to denote a package internal functions, it may lead to
confusion.
What these functions (classy prelude/my library spin-off) do is run a
computation, isolating it from the calling thread (through async) and
catching all inner exceptions (of either synchronous or asynchronous
type, raised by either throwIO or throwTo instructions _present
somewhere inside that computation_, or by the RTS but once again
affecting only that computation, not the calling one.
The calling one is thus 'free' to receive asynchronous exceptions in
the meantime (the execution of the inner computation).
Thus, I propose either:
Control.Exception.Inner / Control.Exception.Enclosed
And/or, possibly also rename the functions to something like:
catchAnyInner / catchAnyEnclosed
Although I do not like this last option so much, the function name
gets too long, but that's a personal preference.
What do you think?
João
2014-02-06 Michael Snoyman
On Thu, Feb 6, 2014 at 8:17 AM, Roman Cheplyaka
wrote: Am I getting this right?
Not quite.
The enclosed computation may get asynchronous exceptions whatever definition of 'asynchronous' you use -- the exact one (by throw method) or the approximate one (by type).
Just a couple of examples:
* The thread may catch an async exception from the RTS (such as BlockedIndefinitelyOnMVar or StackOverflow) * The thread may spawn other threads, passing its pid to them, and one of its children may eventually kill it
So I'd say this method allows to catch any exceptions "related" to the computation, synchronous or asynchronous. It is this "relatedness" that is enforced by running it in a separate thread.
Roman
I definitely think this is important to get our terminology right. A lot of the scariness of async exceptions likely spawns from the fact that we use the same term to refer to a number of very different cases. Let me give a crack at breaking down exceptions:
* An exception with a synchronous type (e.g., IOException) thrown via throwIO. This is the most synchronous of synchronous exceptions. * An exception with an asynchronous type (e.g., UserInterrupt) thrown via throwIO. There's legitimate room for debate as to what we should call this. For my purposes, I'd want to call it a synchronous exception. * An exception with a synchronous type thrown via throwTo. Similar to previous bullet, but I'd consider this asynchronous. * An exception with an asynchronous type thrown via throwTo. This is solidly an asynchronous exception.
Then we have some more interesting questions:
* What *is* an asynchronous type? By including BlockedIndefinitelyOnMVar, it seems like you're defining it to include any exception generated by the RTS. However, I'd consider it a synchronous exception: it is generated in direct consequence of performing an IO action. It just happens to be generated by the RTS instead of via some library talking to the filesystem. * What happens if an async exception is caught and then rethrown? Has it transformed itself into a synchronous exception? That's a tricky question, and likely depends on the exact manner in which is was caught. * What happens if a function utilizes some form of asynchronous exception mechanism to affect its behavior? The prime example of this is `timeout`, or better, the `asyncTimeout` function I displayed above. Internally to that function, I think that's an async exception. However, for a *caller* of that function, the behavior is actually synchronous: there was no notification from the outside world changing the behavior of this function, it simply has the possibility to terminate by throwing a Timeout, the same way a function may terminate by throwing an IOException.
That last bullet is crucial to the question of whether classy-prelude's and João's catching functions are asynchronous or not. But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do.
Michael

I like the idea of renaming the module to reflect this concept (I'm fine
with either Inner or Enclosed), but leaving the function names themselves
as-is.
On Thu, Feb 6, 2014 at 2:12 PM, João Cristóvão
Thanks Roman and Michael for the latest clarifications:
I had indeed forgot the case where a thread runned in catchAny spawn child threads that kill their parent.
But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do.
The word currently in my head is 'inner', although Roman's suggestion of 'enclosed' looks fine too. Internal is also correct, but as it is regularly used to denote a package internal functions, it may lead to confusion.
What these functions (classy prelude/my library spin-off) do is run a computation, isolating it from the calling thread (through async) and catching all inner exceptions (of either synchronous or asynchronous type, raised by either throwIO or throwTo instructions _present somewhere inside that computation_, or by the RTS but once again affecting only that computation, not the calling one.
The calling one is thus 'free' to receive asynchronous exceptions in the meantime (the execution of the inner computation).
Thus, I propose either:
Control.Exception.Inner / Control.Exception.Enclosed
And/or, possibly also rename the functions to something like:
catchAnyInner / catchAnyEnclosed
Although I do not like this last option so much, the function name gets too long, but that's a personal preference.
What do you think? João
2014-02-06 Michael Snoyman
: On Thu, Feb 6, 2014 at 8:17 AM, Roman Cheplyaka
Am I getting this right?
Not quite.
The enclosed computation may get asynchronous exceptions whatever definition of 'asynchronous' you use -- the exact one (by throw method) or the approximate one (by type).
Just a couple of examples:
* The thread may catch an async exception from the RTS (such as BlockedIndefinitelyOnMVar or StackOverflow) * The thread may spawn other threads, passing its pid to them, and one of its children may eventually kill it
So I'd say this method allows to catch any exceptions "related" to the computation, synchronous or asynchronous. It is this "relatedness" that is enforced by running it in a separate thread.
Roman
I definitely think this is important to get our terminology right. A lot of the scariness of async exceptions likely spawns from the fact that we use the same term to refer to a number of very different cases. Let me give a crack at breaking down exceptions:
* An exception with a synchronous type (e.g., IOException) thrown via throwIO. This is the most synchronous of synchronous exceptions. * An exception with an asynchronous type (e.g., UserInterrupt) thrown via throwIO. There's legitimate room for debate as to what we should call
For my purposes, I'd want to call it a synchronous exception. * An exception with a synchronous type thrown via throwTo. Similar to previous bullet, but I'd consider this asynchronous. * An exception with an asynchronous type thrown via throwTo. This is solidly an asynchronous exception.
Then we have some more interesting questions:
* What *is* an asynchronous type? By including BlockedIndefinitelyOnMVar, it seems like you're defining it to include any exception generated by the RTS. However, I'd consider it a synchronous exception: it is generated in
consequence of performing an IO action. It just happens to be generated by the RTS instead of via some library talking to the filesystem. * What happens if an async exception is caught and then rethrown? Has it transformed itself into a synchronous exception? That's a tricky question, and likely depends on the exact manner in which is was caught. * What happens if a function utilizes some form of asynchronous exception mechanism to affect its behavior? The prime example of this is `timeout`, or better, the `asyncTimeout` function I displayed above. Internally to that function, I think that's an async exception. However, for a *caller* of
wrote: this. direct that
function, the behavior is actually synchronous: there was no notification from the outside world changing the behavior of this function, it simply has the possibility to terminate by throwing a Timeout, the same way a function may terminate by throwing an IOException.
That last bullet is crucial to the question of whether classy-prelude's and João's catching functions are asynchronous or not. But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do.
Michael

Just to let you know, the enclosed-exceptions is now at Hackage, allowing
you to use the functions previously discussed without adding the heavier
dependency on Classy Prelude.
http://hackage.haskell.org/package/enclosed-exceptions
Cheers,
Joao
2014-02-06 12:35 GMT+00:00 Michael Snoyman
I like the idea of renaming the module to reflect this concept (I'm fine with either Inner or Enclosed), but leaving the function names themselves as-is.
On Thu, Feb 6, 2014 at 2:12 PM, João Cristóvão
wrote: Thanks Roman and Michael for the latest clarifications:
I had indeed forgot the case where a thread runned in catchAny spawn child threads that kill their parent.
But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do.
The word currently in my head is 'inner', although Roman's suggestion of 'enclosed' looks fine too. Internal is also correct, but as it is regularly used to denote a package internal functions, it may lead to confusion.
What these functions (classy prelude/my library spin-off) do is run a computation, isolating it from the calling thread (through async) and catching all inner exceptions (of either synchronous or asynchronous type, raised by either throwIO or throwTo instructions _present somewhere inside that computation_, or by the RTS but once again affecting only that computation, not the calling one.
The calling one is thus 'free' to receive asynchronous exceptions in the meantime (the execution of the inner computation).
Thus, I propose either:
Control.Exception.Inner / Control.Exception.Enclosed
And/or, possibly also rename the functions to something like:
catchAnyInner / catchAnyEnclosed
Although I do not like this last option so much, the function name gets too long, but that's a personal preference.
What do you think? João
2014-02-06 Michael Snoyman
: On Thu, Feb 6, 2014 at 8:17 AM, Roman Cheplyaka
Am I getting this right?
Not quite.
The enclosed computation may get asynchronous exceptions whatever definition of 'asynchronous' you use -- the exact one (by throw method) or the approximate one (by type).
Just a couple of examples:
* The thread may catch an async exception from the RTS (such as BlockedIndefinitelyOnMVar or StackOverflow) * The thread may spawn other threads, passing its pid to them, and one of its children may eventually kill it
So I'd say this method allows to catch any exceptions "related" to the computation, synchronous or asynchronous. It is this "relatedness" that is enforced by running it in a separate thread.
Roman
I definitely think this is important to get our terminology right. A lot of the scariness of async exceptions likely spawns from the fact that we use the same term to refer to a number of very different cases. Let me give a crack at breaking down exceptions:
* An exception with a synchronous type (e.g., IOException) thrown via throwIO. This is the most synchronous of synchronous exceptions. * An exception with an asynchronous type (e.g., UserInterrupt) thrown via throwIO. There's legitimate room for debate as to what we should call
For my purposes, I'd want to call it a synchronous exception. * An exception with a synchronous type thrown via throwTo. Similar to previous bullet, but I'd consider this asynchronous. * An exception with an asynchronous type thrown via throwTo. This is solidly an asynchronous exception.
Then we have some more interesting questions:
* What *is* an asynchronous type? By including BlockedIndefinitelyOnMVar, it seems like you're defining it to include any exception generated by the RTS. However, I'd consider it a synchronous exception: it is generated in
consequence of performing an IO action. It just happens to be generated by the RTS instead of via some library talking to the filesystem. * What happens if an async exception is caught and then rethrown? Has it transformed itself into a synchronous exception? That's a tricky question, and likely depends on the exact manner in which is was caught. * What happens if a function utilizes some form of asynchronous exception mechanism to affect its behavior? The prime example of this is `timeout`, or better, the `asyncTimeout` function I displayed above. Internally to
function, I think that's an async exception. However, for a *caller* of
wrote: this. direct that that
function, the behavior is actually synchronous: there was no notification from the outside world changing the behavior of this function, it simply has the possibility to terminate by throwing a Timeout, the same way a function may terminate by throwing an IOException.
That last bullet is crucial to the question of whether classy-prelude's and João's catching functions are asynchronous or not. But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do.
Michael

Hi, I’m playing the “do we really need more packages with <10 symbols” card again: Am Mittwoch, den 05.02.2014, 13:23 +0200 schrieb Roman Cheplyaka:
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
isn’t that better done in base-compat, which provides exactly that: The scope of base-compat is to provides the same functionality as the latest version of base for a wider range of compilers.
* define convenient functions for catching only synchronous exceptions
If they are convenient, maybe they should go into base? (I don’t mind such micro-packages if they are a vehicle for design space exploration and experiments, but I do think we should avoid too many packages aimed for general, stable, real-world-use if we can help it.) Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0x4743206C Debian Developer: nomeata@debian.org

* Joachim Breitner
Hi,
I’m playing the “do we really need more packages with <10 symbols” card again:
"We"? This is about the time I stop pretending that there are any "we" with identical interests. "We" consist of many individuals, each one with his/her own agenda. Every decision is associated with different costs and benefits for each agent. In this case, the cost for me is very low (a couple of hours or less) and the benefit is huge — the package does exactly what I need it to do. The alternative you propose below is very costly (time spent arguing for the changes and waiting for them to be applied), and the benefit is the same at best. Of course, if you persuade me that my decision bears significant cost for others, I'll be a nice guy and cooperate (esp. if others are willing to put some effort, too, because it's them who the alternative decision will presumably benefit). But so far this cost is not obvious to me at all. Furthermore, *assuming* there is indeed cost to others, they can improve the situation directly. Indeed, I already did at least some part of the job (wrote the code that can be directly copied to the packages you mention). Why don't others do the second part of the job, that they like to say is almost trivial, and put their time and effort where their mouth is?
Am Mittwoch, den 05.02.2014, 13:23 +0200 schrieb Roman Cheplyaka:
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
isn’t that better done in base-compat, which provides exactly that: The scope of base-compat is to provides the same functionality as the latest version of base for a wider range of compilers.
* define convenient functions for catching only synchronous exceptions
If they are convenient, maybe they should go into base?
(I don’t mind such micro-packages if they are a vehicle for design space exploration and experiments, but I do think we should avoid too many packages aimed for general, stable, real-world-use if we can help it.)
Greetings, Joachim

Be aware that "passing through" of asynchronous exceptions is not really
possible. There simply is no way to selectively catch an exception -- one
must always catch and rethrow, thus turning asynchronous exceptions into
synchronous exceptions. See http://www.edsko.net/2013/06/11/throwto/ for
details.
Edsko
On Wed, Feb 5, 2014 at 11:23 AM, Roman Cheplyaka
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
David Sorokin
-
Edsko de Vries
-
Joachim Breitner
-
João Cristóvão
-
Michael Snoyman
-
Roman Cheplyaka