
* 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