1
+ {-# LANGUAGE DataKinds #-}
1
2
{-# LANGUAGE DefaultSignatures #-}
2
3
{-# LANGUAGE FlexibleContexts #-}
4
+ {-# LANGUAGE GADTs #-}
3
5
{-# LANGUAGE MultiParamTypeClasses #-}
4
6
{-# LANGUAGE QuantifiedConstraints #-}
5
7
{-# LANGUAGE RankNTypes #-}
6
8
{-# LANGUAGE ScopedTypeVariables #-}
7
9
{-# LANGUAGE TypeApplications #-}
8
10
{-# LANGUAGE TypeFamilies #-}
9
11
{-# LANGUAGE TypeFamilyDependencies #-}
10
-
12
+ -- MonadAsync's ReaderT instance is undecidable.
13
+ {-# LANGUAGE UndecidableInstances #-}
11
14
module Control.Monad.Class.MonadAsync
12
15
( MonadAsync (.. )
13
16
, AsyncCancelled (.. )
@@ -34,10 +37,14 @@ import Control.Monad.Class.MonadSTM
34
37
import Control.Monad.Class.MonadThrow
35
38
import Control.Monad.Class.MonadTimer
36
39
40
+ import Control.Monad.Trans (lift )
41
+ import Control.Monad.Reader (ReaderT (.. ))
42
+
37
43
import Control.Concurrent.Async (AsyncCancelled (.. ))
38
44
import qualified Control.Concurrent.Async as Async
39
45
import qualified Control.Exception as E
40
46
47
+ import Data.Bifunctor (first )
41
48
import Data.Foldable (fold )
42
49
import Data.Functor (void )
43
50
import Data.Kind (Type )
@@ -390,3 +397,77 @@ forkRepeat label action =
390
397
391
398
tryAll :: MonadCatch m => m a -> m (Either SomeException a )
392
399
tryAll = try
400
+
401
+
402
+ --
403
+ -- ReaderT instance
404
+ --
405
+
406
+ newtype WrappedAsync r (m :: Type -> Type ) a =
407
+ WrappedAsync { unWrapAsync :: Async m a }
408
+
409
+ instance ( MonadAsync m
410
+ , MonadCatch (STM m )
411
+ ) => MonadAsync (ReaderT r m ) where
412
+ type Async (ReaderT r m ) = WrappedAsync r m
413
+ asyncThreadId (WrappedAsync a) = asyncThreadId a
414
+
415
+ async (ReaderT ma) = ReaderT $ \ r -> WrappedAsync <$> async (ma r)
416
+ withAsync (ReaderT ma) f = ReaderT $ \ r -> withAsync (ma r)
417
+ $ \ a -> runReaderT (f (WrappedAsync a)) r
418
+ asyncWithUnmask f = ReaderT $ \ r -> fmap WrappedAsync
419
+ $ asyncWithUnmask
420
+ $ \ unmask -> runReaderT (f (liftF unmask)) r
421
+ where
422
+ liftF :: (m a -> m a ) -> ReaderT r m a -> ReaderT r m a
423
+ liftF g (ReaderT r) = ReaderT (g . r)
424
+
425
+ waitCatchSTM = WrappedSTM . waitCatchSTM . unWrapAsync
426
+ pollSTM = WrappedSTM . pollSTM . unWrapAsync
427
+
428
+ race (ReaderT ma) (ReaderT mb) = ReaderT $ \ r -> race (ma r) (mb r)
429
+ race_ (ReaderT ma) (ReaderT mb) = ReaderT $ \ r -> race_ (ma r) (mb r)
430
+ concurrently (ReaderT ma) (ReaderT mb) = ReaderT $ \ r -> concurrently (ma r) (mb r)
431
+
432
+ wait = lift . wait . unWrapAsync
433
+ poll = lift . poll . unWrapAsync
434
+ waitCatch = lift . waitCatch . unWrapAsync
435
+ cancel = lift . cancel . unWrapAsync
436
+ uninterruptibleCancel = lift . uninterruptibleCancel
437
+ . unWrapAsync
438
+ cancelWith = (lift .: cancelWith)
439
+ . unWrapAsync
440
+ waitAny = fmap (first WrappedAsync )
441
+ . lift . waitAny
442
+ . map unWrapAsync
443
+ waitAnyCatch = fmap (first WrappedAsync )
444
+ . lift . waitAnyCatch
445
+ . map unWrapAsync
446
+ waitAnyCancel = fmap (first WrappedAsync )
447
+ . lift . waitAnyCancel
448
+ . map unWrapAsync
449
+ waitAnyCatchCancel = fmap (first WrappedAsync )
450
+ . lift . waitAnyCatchCancel
451
+ . map unWrapAsync
452
+ waitEither = on (lift .: waitEither) unWrapAsync
453
+ waitEitherCatch = on (lift .: waitEitherCatch) unWrapAsync
454
+ waitEitherCancel = on (lift .: waitEitherCancel) unWrapAsync
455
+ waitEitherCatchCancel = on (lift .: waitEitherCatchCancel) unWrapAsync
456
+ waitEither_ = on (lift .: waitEither_) unWrapAsync
457
+ waitBoth = on (lift .: waitBoth) unWrapAsync
458
+
459
+
460
+ --
461
+ -- Utilities
462
+ --
463
+
464
+ (.:) :: (c -> d ) -> (a -> b -> c ) -> (a -> b -> d )
465
+ (f .: g) x y = f (g x y)
466
+
467
+
468
+ -- | A higher order version of 'Data.Function.on'
469
+ --
470
+ on :: (f a -> f b -> c )
471
+ -> (forall x . g x -> f x )
472
+ -> (g a -> g b -> c )
473
+ on f g = \ a b -> f (g a) (g b)
0 commit comments