Skip to content

Commit aa03c27

Browse files
committed
feat: support for exception context propagation
This is a WIP in order to have exception context propagation. Instead of `catch`ing and `throw`ing, we `catchNoPropagate` and `rethrow`: - `catchNoPropagate` does not add the `WhileHandling` logic onto the exception (this is to be discussed, maybe we want to add a bit of context) - `rethrow` does not add / override the backtrace. I had to change many of the type signature of the library in a backward incompatible manner AND this is only compatible with GHC 9.12 for now. I will use this commit at work for a bit of time in order to gather some feedback and maybe comeback with a more robust solution. Example of usage / changes: The following code: ```haskell {-# LANGUAGE DeriveAnyClass #-} import Control.Concurrent.Async import Control.Exception import Control.Exception.Context import Control.Exception.Annotation import Data.Typeable import Data.Traversable import GHC.Stack data Ann = Ann String deriving (Show, ExceptionAnnotation) asyncTask :: HasCallStack => IO () asyncTask = annotateIO (Ann "bonjour") $ do error "yoto" asyncTask' :: HasCallStack => IO () asyncTask' = annotateIO (Ann "bonjour2") $ do error "yutu" main = do -- withAsync asyncTask wait concurrently asyncTask asyncTask' -- race asyncTask asyncTask' ``` When run without this commit leads to: ``` ASyncException.hs: Uncaught exception ghc-internal:GHC.Internal.Exception.ErrorCall: yoto HasCallStack backtrace: throwIO, called at ./Control/Concurrent/Async/Internal.hs:630:24 in async-2.2.5-50rpfAJ7BEc1o5OswtTMUN:Control.Concurrent.Async.Internal ``` When run with this commit: ``` *** Exception: yoto Ann "bonjour" HasCallStack backtrace: error, called at /home/guillaume//ASyncException.hs:15:3 in async-2.2.5-inplace:Main asyncTask, called at /home/guillaume//ASyncException.hs:23:16 in async-2.2.5-inplace:Main ```
1 parent 7ac0e51 commit aa03c27

File tree

1 file changed

+37
-31
lines changed

1 file changed

+37
-31
lines changed

Control/Concurrent/Async/Internal.hs

Lines changed: 37 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ import Data.IORef
5656
import GHC.Exts
5757
import GHC.IO hiding (finally, onException)
5858
import GHC.Conc (ThreadId(..))
59+
import Control.Exception.Context
5960

6061
-- -----------------------------------------------------------------------------
6162
-- STM Async API
@@ -70,7 +71,7 @@ data Async a = Async
7071
{ asyncThreadId :: {-# UNPACK #-} !ThreadId
7172
-- ^ Returns the 'ThreadId' of the thread running
7273
-- the given 'Async'.
73-
, _asyncWait :: STM (Either SomeException a)
74+
, _asyncWait :: STM (Either (ExceptionWithContext SomeException) a)
7475
}
7576

7677
instance Eq (Async a) where
@@ -178,11 +179,16 @@ withAsyncUsing :: (IO () -> IO ThreadId)
178179
withAsyncUsing doFork = \action inner -> do
179180
var <- newEmptyTMVarIO
180181
mask $ \restore -> do
181-
t <- doFork $ try (restore action) >>= atomically . putTMVar var
182+
t <- doFork $ tryWithContext (restore action) >>= atomically . putTMVar var
182183
let a = Async t (readTMVar var)
183-
r <- restore (inner a) `catchAll` \e -> do
184+
r <- restore (inner a) `catchAll` \e@(ExceptionWithContext ctx e') -> do
184185
uninterruptibleCancel a
185-
throwIO e
186+
print "e"
187+
print $ displayException e
188+
print "context"
189+
print $ displayExceptionContext ctx
190+
print "/context"
191+
rethrowIO e
186192
uninterruptibleCancel a
187193
return r
188194

@@ -206,7 +212,7 @@ wait = tryAgain . atomically . waitSTM
206212
-- > waitCatch = atomically . waitCatchSTM
207213
--
208214
{-# INLINE waitCatch #-}
209-
waitCatch :: Async a -> IO (Either SomeException a)
215+
waitCatch :: Async a -> IO (Either (ExceptionWithContext SomeException) a)
210216
waitCatch = tryAgain . atomically . waitCatchSTM
211217
where
212218
-- See: https://github.com/simonmar/async/issues/14
@@ -220,7 +226,7 @@ waitCatch = tryAgain . atomically . waitCatchSTM
220226
-- > poll = atomically . pollSTM
221227
--
222228
{-# INLINE poll #-}
223-
poll :: Async a -> IO (Maybe (Either SomeException a))
229+
poll :: Async a -> IO (Maybe (Either (ExceptionWithContext SomeException) a))
224230
poll = atomically . pollSTM
225231

226232
-- | A version of 'wait' that can be used inside an STM transaction.
@@ -233,13 +239,13 @@ waitSTM a = do
233239
-- | A version of 'waitCatch' that can be used inside an STM transaction.
234240
--
235241
{-# INLINE waitCatchSTM #-}
236-
waitCatchSTM :: Async a -> STM (Either SomeException a)
242+
waitCatchSTM :: Async a -> STM (Either (ExceptionWithContext SomeException) a)
237243
waitCatchSTM (Async _ w) = w
238244

239245
-- | A version of 'poll' that can be used inside an STM transaction.
240246
--
241247
{-# INLINE pollSTM #-}
242-
pollSTM :: Async a -> STM (Maybe (Either SomeException a))
248+
pollSTM :: Async a -> STM (Maybe (Either (ExceptionWithContext SomeException) a))
243249
pollSTM (Async _ w) = (Just <$> w) `orElse` return Nothing
244250

245251
-- | Cancel an asynchronous action by throwing the @AsyncCancelled@
@@ -310,13 +316,13 @@ cancelWith a@(Async t _) e = throwTo t e <* waitCatch a
310316
-- returned corresponds to the first completed 'Async' in the list.
311317
--
312318
{-# INLINE waitAnyCatch #-}
313-
waitAnyCatch :: [Async a] -> IO (Async a, Either SomeException a)
319+
waitAnyCatch :: [Async a] -> IO (Async a, Either (ExceptionWithContext SomeException) a)
314320
waitAnyCatch = atomically . waitAnyCatchSTM
315321

316322
-- | A version of 'waitAnyCatch' that can be used inside an STM transaction.
317323
--
318324
-- @since 2.1.0
319-
waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a)
325+
waitAnyCatchSTM :: [Async a] -> STM (Async a, Either (ExceptionWithContext SomeException) a)
320326
waitAnyCatchSTM [] =
321327
throwSTM $ ErrorCall
322328
"waitAnyCatchSTM: invalid argument: input list must be non-empty"
@@ -327,7 +333,7 @@ waitAnyCatchSTM asyncs =
327333
-- | Like 'waitAnyCatch', but also cancels the other asynchronous
328334
-- operations as soon as one has completed.
329335
--
330-
waitAnyCatchCancel :: [Async a] -> IO (Async a, Either SomeException a)
336+
waitAnyCatchCancel :: [Async a] -> IO (Async a, Either (ExceptionWithContext SomeException) a)
331337
waitAnyCatchCancel asyncs =
332338
waitAnyCatch asyncs `finally` cancelMany asyncs
333339

@@ -364,8 +370,8 @@ waitAnyCancel asyncs =
364370
-- | Wait for the first of two @Async@s to finish.
365371
{-# INLINE waitEitherCatch #-}
366372
waitEitherCatch :: Async a -> Async b
367-
-> IO (Either (Either SomeException a)
368-
(Either SomeException b))
373+
-> IO (Either (Either (ExceptionWithContext SomeException) a)
374+
(Either (ExceptionWithContext SomeException) b))
369375
waitEitherCatch left right =
370376
tryAgain $ atomically (waitEitherCatchSTM left right)
371377
where
@@ -376,8 +382,8 @@ waitEitherCatch left right =
376382
--
377383
-- @since 2.1.0
378384
waitEitherCatchSTM :: Async a -> Async b
379-
-> STM (Either (Either SomeException a)
380-
(Either SomeException b))
385+
-> STM (Either (Either (ExceptionWithContext SomeException) a)
386+
(Either (ExceptionWithContext SomeException) b))
381387
waitEitherCatchSTM left right =
382388
(Left <$> waitCatchSTM left)
383389
`orElse`
@@ -387,8 +393,8 @@ waitEitherCatchSTM left right =
387393
-- returning.
388394
--
389395
waitEitherCatchCancel :: Async a -> Async b
390-
-> IO (Either (Either SomeException a)
391-
(Either SomeException b))
396+
-> IO (Either (Either (ExceptionWithContext SomeException) a)
397+
(Either (ExceptionWithContext SomeException) b))
392398
waitEitherCatchCancel left right =
393399
waitEitherCatch left right `finally` cancelMany [() <$ left, () <$ right]
394400

@@ -458,7 +464,7 @@ waitBothSTM left right = do
458464
-- Linking threads
459465

460466
data ExceptionInLinkedThread =
461-
forall a . ExceptionInLinkedThread (Async a) SomeException
467+
forall a . ExceptionInLinkedThread (Async a) (ExceptionWithContext SomeException)
462468
#if __GLASGOW_HASKELL__ < 710
463469
deriving Typeable
464470
#endif
@@ -496,7 +502,7 @@ link = linkOnly (not . isCancel)
496502
-- thread should be propagated to the source thread.
497503
--
498504
linkOnly
499-
:: (SomeException -> Bool) -- ^ return 'True' if the exception
505+
:: (ExceptionWithContext SomeException -> Bool) -- ^ return 'True' if the exception
500506
-- should be propagated, 'False'
501507
-- otherwise.
502508
-> Async a
@@ -527,7 +533,7 @@ link2 = link2Only (not . isCancel)
527533
-- The supplied predicate determines which exceptions in the target
528534
-- thread should be propagated to the source thread.
529535
--
530-
link2Only :: (SomeException -> Bool) -> Async a -> Async b -> IO ()
536+
link2Only :: (ExceptionWithContext SomeException -> Bool) -> Async a -> Async b -> IO ()
531537
link2Only shouldThrow left@(Async tl _) right@(Async tr _) =
532538
void $ forkRepeat $ do
533539
r <- waitEitherCatch left right
@@ -538,8 +544,8 @@ link2Only shouldThrow left@(Async tl _) right@(Async tr _) =
538544
throwTo tl (ExceptionInLinkedThread right e)
539545
_ -> return ()
540546

541-
isCancel :: SomeException -> Bool
542-
isCancel e
547+
isCancel :: (ExceptionWithContext SomeException) -> Bool
548+
isCancel (ExceptionWithContext ctx e)
543549
| Just AsyncCancelled <- fromException e = True
544550
| otherwise = False
545551

@@ -613,7 +619,7 @@ race left right = concurrently' left right collect
613619
collect m = do
614620
e <- m
615621
case e of
616-
Left ex -> throwIO ex
622+
Left ex -> rethrowIO ex
617623
Right r -> return r
618624

619625
-- race_ :: IO a -> IO b -> IO ()
@@ -627,7 +633,7 @@ concurrently left right = concurrently' left right (collect [])
627633
collect xs m = do
628634
e <- m
629635
case e of
630-
Left ex -> throwIO ex
636+
Left ex -> rethrowIO ex
631637
Right r -> collect (r:xs) m
632638

633639
-- concurrentlyE :: IO (Either e a) -> IO (Either e b) -> IO (Either e (a, b))
@@ -640,11 +646,11 @@ concurrentlyE left right = concurrently' left right (collect [])
640646
collect xs m = do
641647
e <- m
642648
case e of
643-
Left ex -> throwIO ex
649+
Left ex -> rethrowIO ex
644650
Right r -> collect (r:xs) m
645651

646652
concurrently' :: IO a -> IO b
647-
-> (IO (Either SomeException (Either a b)) -> IO r)
653+
-> (IO (Either (ExceptionWithContext SomeException) (Either a b)) -> IO r)
648654
-> IO r
649655
concurrently' left right collect = do
650656
done <- newEmptyMVar
@@ -699,7 +705,7 @@ concurrently_ left right = concurrently' left right (collect 0)
699705
collect i m = do
700706
e <- m
701707
case e of
702-
Left ex -> throwIO ex
708+
Left ex -> rethrowIO ex
703709
Right _ -> collect (i + 1 :: Int) m
704710

705711

@@ -854,11 +860,11 @@ forkRepeat action =
854860
_ -> return ()
855861
in forkIO go
856862

857-
catchAll :: IO a -> (SomeException -> IO a) -> IO a
858-
catchAll = catch
863+
catchAll :: IO a -> (ExceptionWithContext SomeException -> IO a) -> IO a
864+
catchAll = catchNoPropagate
859865

860-
tryAll :: IO a -> IO (Either SomeException a)
861-
tryAll = try
866+
tryAll :: IO a -> IO (Either (ExceptionWithContext SomeException) a)
867+
tryAll = tryWithContext
862868

863869
-- A version of forkIO that does not include the outer exception
864870
-- handler: saves a bit of time when we will be installing our own

0 commit comments

Comments
 (0)