@@ -56,6 +56,7 @@ import Data.IORef
56
56
import GHC.Exts
57
57
import GHC.IO hiding (finally , onException )
58
58
import GHC.Conc (ThreadId (.. ))
59
+ import Control.Exception.Context
59
60
60
61
-- -----------------------------------------------------------------------------
61
62
-- STM Async API
@@ -70,7 +71,7 @@ data Async a = Async
70
71
{ asyncThreadId :: {-# UNPACK #-} ! ThreadId
71
72
-- ^ Returns the 'ThreadId' of the thread running
72
73
-- the given 'Async'.
73
- , _asyncWait :: STM (Either SomeException a )
74
+ , _asyncWait :: STM (Either ( ExceptionWithContext SomeException ) a )
74
75
}
75
76
76
77
instance Eq (Async a ) where
@@ -178,11 +179,16 @@ withAsyncUsing :: (IO () -> IO ThreadId)
178
179
withAsyncUsing doFork = \ action inner -> do
179
180
var <- newEmptyTMVarIO
180
181
mask $ \ restore -> do
181
- t <- doFork $ try (restore action) >>= atomically . putTMVar var
182
+ t <- doFork $ tryWithContext (restore action) >>= atomically . putTMVar var
182
183
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
184
185
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
186
192
uninterruptibleCancel a
187
193
return r
188
194
@@ -206,7 +212,7 @@ wait = tryAgain . atomically . waitSTM
206
212
-- > waitCatch = atomically . waitCatchSTM
207
213
--
208
214
{-# INLINE waitCatch #-}
209
- waitCatch :: Async a -> IO (Either SomeException a )
215
+ waitCatch :: Async a -> IO (Either ( ExceptionWithContext SomeException ) a )
210
216
waitCatch = tryAgain . atomically . waitCatchSTM
211
217
where
212
218
-- See: https://github.com/simonmar/async/issues/14
@@ -220,7 +226,7 @@ waitCatch = tryAgain . atomically . waitCatchSTM
220
226
-- > poll = atomically . pollSTM
221
227
--
222
228
{-# INLINE poll #-}
223
- poll :: Async a -> IO (Maybe (Either SomeException a ))
229
+ poll :: Async a -> IO (Maybe (Either ( ExceptionWithContext SomeException ) a ))
224
230
poll = atomically . pollSTM
225
231
226
232
-- | A version of 'wait' that can be used inside an STM transaction.
@@ -233,13 +239,13 @@ waitSTM a = do
233
239
-- | A version of 'waitCatch' that can be used inside an STM transaction.
234
240
--
235
241
{-# INLINE waitCatchSTM #-}
236
- waitCatchSTM :: Async a -> STM (Either SomeException a )
242
+ waitCatchSTM :: Async a -> STM (Either ( ExceptionWithContext SomeException ) a )
237
243
waitCatchSTM (Async _ w) = w
238
244
239
245
-- | A version of 'poll' that can be used inside an STM transaction.
240
246
--
241
247
{-# INLINE pollSTM #-}
242
- pollSTM :: Async a -> STM (Maybe (Either SomeException a ))
248
+ pollSTM :: Async a -> STM (Maybe (Either ( ExceptionWithContext SomeException ) a ))
243
249
pollSTM (Async _ w) = (Just <$> w) `orElse` return Nothing
244
250
245
251
-- | Cancel an asynchronous action by throwing the @AsyncCancelled@
@@ -310,13 +316,13 @@ cancelWith a@(Async t _) e = throwTo t e <* waitCatch a
310
316
-- returned corresponds to the first completed 'Async' in the list.
311
317
--
312
318
{-# INLINE waitAnyCatch #-}
313
- waitAnyCatch :: [Async a ] -> IO (Async a , Either SomeException a )
319
+ waitAnyCatch :: [Async a ] -> IO (Async a , Either ( ExceptionWithContext SomeException ) a )
314
320
waitAnyCatch = atomically . waitAnyCatchSTM
315
321
316
322
-- | A version of 'waitAnyCatch' that can be used inside an STM transaction.
317
323
--
318
324
-- @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 )
320
326
waitAnyCatchSTM [] =
321
327
throwSTM $ ErrorCall
322
328
" waitAnyCatchSTM: invalid argument: input list must be non-empty"
@@ -327,7 +333,7 @@ waitAnyCatchSTM asyncs =
327
333
-- | Like 'waitAnyCatch', but also cancels the other asynchronous
328
334
-- operations as soon as one has completed.
329
335
--
330
- waitAnyCatchCancel :: [Async a ] -> IO (Async a , Either SomeException a )
336
+ waitAnyCatchCancel :: [Async a ] -> IO (Async a , Either ( ExceptionWithContext SomeException ) a )
331
337
waitAnyCatchCancel asyncs =
332
338
waitAnyCatch asyncs `finally` cancelMany asyncs
333
339
@@ -364,8 +370,8 @@ waitAnyCancel asyncs =
364
370
-- | Wait for the first of two @Async@s to finish.
365
371
{-# INLINE waitEitherCatch #-}
366
372
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 ))
369
375
waitEitherCatch left right =
370
376
tryAgain $ atomically (waitEitherCatchSTM left right)
371
377
where
@@ -376,8 +382,8 @@ waitEitherCatch left right =
376
382
--
377
383
-- @since 2.1.0
378
384
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 ))
381
387
waitEitherCatchSTM left right =
382
388
(Left <$> waitCatchSTM left)
383
389
`orElse`
@@ -387,8 +393,8 @@ waitEitherCatchSTM left right =
387
393
-- returning.
388
394
--
389
395
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 ))
392
398
waitEitherCatchCancel left right =
393
399
waitEitherCatch left right `finally` cancelMany [() <$ left, () <$ right]
394
400
@@ -458,7 +464,7 @@ waitBothSTM left right = do
458
464
-- Linking threads
459
465
460
466
data ExceptionInLinkedThread =
461
- forall a . ExceptionInLinkedThread (Async a ) SomeException
467
+ forall a . ExceptionInLinkedThread (Async a ) ( ExceptionWithContext SomeException )
462
468
#if __GLASGOW_HASKELL__ < 710
463
469
deriving Typeable
464
470
#endif
@@ -496,7 +502,7 @@ link = linkOnly (not . isCancel)
496
502
-- thread should be propagated to the source thread.
497
503
--
498
504
linkOnly
499
- :: (SomeException -> Bool ) -- ^ return 'True' if the exception
505
+ :: (ExceptionWithContext SomeException -> Bool ) -- ^ return 'True' if the exception
500
506
-- should be propagated, 'False'
501
507
-- otherwise.
502
508
-> Async a
@@ -527,7 +533,7 @@ link2 = link2Only (not . isCancel)
527
533
-- The supplied predicate determines which exceptions in the target
528
534
-- thread should be propagated to the source thread.
529
535
--
530
- link2Only :: (SomeException -> Bool ) -> Async a -> Async b -> IO ()
536
+ link2Only :: (ExceptionWithContext SomeException -> Bool ) -> Async a -> Async b -> IO ()
531
537
link2Only shouldThrow left@ (Async tl _) right@ (Async tr _) =
532
538
void $ forkRepeat $ do
533
539
r <- waitEitherCatch left right
@@ -538,8 +544,8 @@ link2Only shouldThrow left@(Async tl _) right@(Async tr _) =
538
544
throwTo tl (ExceptionInLinkedThread right e)
539
545
_ -> return ()
540
546
541
- isCancel :: SomeException -> Bool
542
- isCancel e
547
+ isCancel :: ( ExceptionWithContext SomeException ) -> Bool
548
+ isCancel ( ExceptionWithContext ctx e)
543
549
| Just AsyncCancelled <- fromException e = True
544
550
| otherwise = False
545
551
@@ -613,7 +619,7 @@ race left right = concurrently' left right collect
613
619
collect m = do
614
620
e <- m
615
621
case e of
616
- Left ex -> throwIO ex
622
+ Left ex -> rethrowIO ex
617
623
Right r -> return r
618
624
619
625
-- race_ :: IO a -> IO b -> IO ()
@@ -627,7 +633,7 @@ concurrently left right = concurrently' left right (collect [])
627
633
collect xs m = do
628
634
e <- m
629
635
case e of
630
- Left ex -> throwIO ex
636
+ Left ex -> rethrowIO ex
631
637
Right r -> collect (r: xs) m
632
638
633
639
-- 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 [])
640
646
collect xs m = do
641
647
e <- m
642
648
case e of
643
- Left ex -> throwIO ex
649
+ Left ex -> rethrowIO ex
644
650
Right r -> collect (r: xs) m
645
651
646
652
concurrently' :: IO a -> IO b
647
- -> (IO (Either SomeException (Either a b )) -> IO r )
653
+ -> (IO (Either ( ExceptionWithContext SomeException ) (Either a b )) -> IO r )
648
654
-> IO r
649
655
concurrently' left right collect = do
650
656
done <- newEmptyMVar
@@ -699,7 +705,7 @@ concurrently_ left right = concurrently' left right (collect 0)
699
705
collect i m = do
700
706
e <- m
701
707
case e of
702
- Left ex -> throwIO ex
708
+ Left ex -> rethrowIO ex
703
709
Right _ -> collect (i + 1 :: Int ) m
704
710
705
711
@@ -854,11 +860,11 @@ forkRepeat action =
854
860
_ -> return ()
855
861
in forkIO go
856
862
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
859
865
860
- tryAll :: IO a -> IO (Either SomeException a )
861
- tryAll = try
866
+ tryAll :: IO a -> IO (Either ( ExceptionWithContext SomeException ) a )
867
+ tryAll = tryWithContext
862
868
863
869
-- A version of forkIO that does not include the outer exception
864
870
-- handler: saves a bit of time when we will be installing our own
0 commit comments