{-# LANGUAGE CPP #-}
{-# LANGUAGE PostfixOperators #-}
{-# OPTIONS_GHC -Wno-duplicate-exports #-}
module Effects.Concurrent.Async
(
MonadAsync (..),
Async,
withAsync,
withAsyncBound,
withAsyncOn,
withAsyncWithUnmask,
withAsyncOnWithUnmask,
wait,
poll,
waitCatch,
Async.asyncThreadId,
cancel,
uninterruptibleCancel,
cancelWith,
Async.AsyncCancelled (..),
race,
race_,
concurrently,
concurrently_,
mapConcurrently,
forConcurrently,
mapConcurrently_,
forConcurrently_,
replicateConcurrently,
replicateConcurrently_,
Concurrently (..),
Async.compareAsyncs,
STM,
Async.waitSTM,
Async.pollSTM,
Async.waitCatchSTM,
waitAny,
waitAnyCatch,
waitAnyCancel,
waitAnyCatchCancel,
waitEither,
waitEitherCatch,
waitEitherCancel,
waitEitherCatchCancel,
waitEither_,
waitBoth,
Async.waitAnySTM,
Async.waitAnyCatchSTM,
Async.waitEitherSTM,
Async.waitEitherCatchSTM,
Async.waitEitherSTM_,
Async.waitBothSTM,
async,
asyncBound,
asyncOn,
asyncWithUnmask,
asyncOnWithUnmask,
link,
linkOnly,
link2,
link2Only,
Async.ExceptionInLinkedThread (..),
pooledMapConcurrentlyN,
pooledMapConcurrently,
pooledMapConcurrentlyN_,
pooledMapConcurrently_,
pooledForConcurrentlyN,
pooledForConcurrently,
pooledForConcurrentlyN_,
pooledForConcurrently_,
pooledReplicateConcurrentlyN,
pooledReplicateConcurrently,
pooledReplicateConcurrentlyN_,
pooledReplicateConcurrently_,
SomeException,
MonadThread,
Positive (MkPositive),
Positive.mkPositive,
Positive.mkPositiveTH,
Positive.unsafePositive,
(+!),
)
where
#if MIN_VERSION_base(4, 18, 0)
import Control.Applicative (Alternative (empty, (<|>)))
#else
import Control.Applicative (Alternative (empty, (<|>)), Applicative (liftA2))
#endif
import Control.Concurrent.Async (Async)
import Control.Concurrent.Async qualified as Async
import Control.Monad (forever, replicateM)
import Control.Monad.Catch (Exception, SomeException)
import Control.Monad.Trans.Class (MonadTrans (lift))
import Control.Monad.Trans.Reader (ReaderT (runReaderT), ask, mapReaderT)
import Data.Foldable (Foldable (fold))
import Data.Functor (void)
import Effects.Concurrent.Thread (MonadThread (threadDelay))
import GHC.Conc (STM)
import GHC.Stack (HasCallStack)
import Numeric.Data.Positive (Positive (MkPositive), (+!))
import Numeric.Data.Positive qualified as Positive
import UnliftIO.Async qualified as UAsync
class (Monad m) => MonadAsync m where
withAsync :: (HasCallStack) => m a -> (Async a -> m b) -> m b
withAsyncBound :: (HasCallStack) => m a -> (Async a -> m b) -> m b
withAsyncOn :: (HasCallStack) => Int -> m a -> (Async a -> m b) -> m b
withAsyncWithUnmask ::
(HasCallStack) =>
((forall c. m c -> m c) -> m a) ->
(Async a -> m b) ->
m b
withAsyncOnWithUnmask ::
(HasCallStack) =>
Int ->
((forall c. m c -> m c) -> m a) ->
(Async a -> m b) ->
m b
wait :: (HasCallStack) => Async a -> m a
poll :: (HasCallStack) => Async a -> m (Maybe (Either SomeException a))
waitCatch :: (HasCallStack) => Async a -> m (Either SomeException a)
cancel :: (HasCallStack) => Async a -> m ()
uninterruptibleCancel :: (HasCallStack) => Async a -> m ()
cancelWith :: (Exception e, HasCallStack) => Async a -> e -> m ()
race :: (HasCallStack) => m a -> m b -> m (Either a b)
concurrently :: (HasCallStack) => m a -> m b -> m (a, b)
concurrently_ :: (HasCallStack) => m a -> m b -> m ()
waitAny :: (HasCallStack) => [Async a] -> m (Async a, a)
waitAnyCatch ::
(HasCallStack) =>
[Async a] ->
m (Async a, Either SomeException a)
waitAnyCancel :: (HasCallStack) => [Async a] -> m (Async a, a)
waitAnyCatchCancel ::
(HasCallStack) =>
[Async a] ->
m (Async a, Either SomeException a)
waitEither :: (HasCallStack) => Async a -> Async b -> m (Either a b)
waitEitherCatch ::
(HasCallStack) =>
Async a ->
Async b ->
m
( Either (Either SomeException a) (Either SomeException b)
)
waitEitherCancel :: (HasCallStack) => Async a -> Async b -> m (Either a b)
waitEitherCatchCancel ::
(HasCallStack) =>
Async a ->
Async b ->
m
( Either
(Either SomeException a)
(Either SomeException b)
)
waitEither_ :: (HasCallStack) => Async a -> Async b -> m ()
waitBoth :: (HasCallStack) => Async a -> Async b -> m (a, b)
async :: (HasCallStack) => m a -> m (Async a)
asyncBound :: (HasCallStack) => m a -> m (Async a)
asyncOn :: (HasCallStack) => Int -> m a -> m (Async a)
asyncWithUnmask :: (HasCallStack) => ((forall b. m b -> m b) -> m a) -> m (Async a)
asyncOnWithUnmask :: (HasCallStack) => Int -> ((forall b. m b -> m b) -> m a) -> m (Async a)
link :: (HasCallStack) => Async a -> m ()
linkOnly :: (HasCallStack) => (SomeException -> Bool) -> Async a -> m ()
link2 :: (HasCallStack) => Async a -> Async b -> m ()
link2Only :: (HasCallStack) => (SomeException -> Bool) -> Async a -> Async b -> m ()
pooledMapConcurrentlyN ::
( HasCallStack,
Traversable t
) =>
Positive Int ->
(a -> m b) ->
t a ->
m (t b)
pooledMapConcurrently ::
( HasCallStack,
Traversable t
) =>
(a -> m b) ->
t a ->
m (t b)
pooledMapConcurrentlyN_ ::
( Foldable f,
HasCallStack
) =>
Positive Int ->
(a -> m b) ->
f a ->
m ()
pooledMapConcurrently_ ::
( Foldable f,
HasCallStack
) =>
(a -> m b) ->
f a ->
m ()
instance MonadAsync IO where
withAsync :: forall a b. HasCallStack => IO a -> (Async a -> IO b) -> IO b
withAsync = IO a -> (Async a -> IO b) -> IO b
forall a b. IO a -> (Async a -> IO b) -> IO b
Async.withAsync
{-# INLINEABLE withAsync #-}
withAsyncBound :: forall a b. HasCallStack => IO a -> (Async a -> IO b) -> IO b
withAsyncBound = IO a -> (Async a -> IO b) -> IO b
forall a b. IO a -> (Async a -> IO b) -> IO b
Async.withAsyncBound
{-# INLINEABLE withAsyncBound #-}
withAsyncOn :: forall a b.
HasCallStack =>
Int -> IO a -> (Async a -> IO b) -> IO b
withAsyncOn = Int -> IO a -> (Async a -> IO b) -> IO b
forall a b. Int -> IO a -> (Async a -> IO b) -> IO b
Async.withAsyncOn
{-# INLINEABLE withAsyncOn #-}
withAsyncWithUnmask :: forall a b.
HasCallStack =>
((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b
withAsyncWithUnmask = ((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b
forall a b.
((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b
Async.withAsyncWithUnmask
{-# INLINEABLE withAsyncWithUnmask #-}
withAsyncOnWithUnmask :: forall a b.
HasCallStack =>
Int
-> ((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b
withAsyncOnWithUnmask = Int
-> ((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b
forall a b.
Int
-> ((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b
Async.withAsyncOnWithUnmask
{-# INLINEABLE withAsyncOnWithUnmask #-}
wait :: forall a. HasCallStack => Async a -> IO a
wait = Async a -> IO a
forall a. Async a -> IO a
Async.wait
{-# INLINEABLE wait #-}
poll :: forall a.
HasCallStack =>
Async a -> IO (Maybe (Either SomeException a))
poll = Async a -> IO (Maybe (Either SomeException a))
forall a. Async a -> IO (Maybe (Either SomeException a))
Async.poll
{-# INLINEABLE poll #-}
waitCatch :: forall a. HasCallStack => Async a -> IO (Either SomeException a)
waitCatch = Async a -> IO (Either SomeException a)
forall a. Async a -> IO (Either SomeException a)
Async.waitCatch
{-# INLINEABLE waitCatch #-}
cancel :: forall a. HasCallStack => Async a -> IO ()
cancel = Async a -> IO ()
forall a. Async a -> IO ()
Async.cancel
{-# INLINEABLE cancel #-}
uninterruptibleCancel :: forall a. HasCallStack => Async a -> IO ()
uninterruptibleCancel = Async a -> IO ()
forall a. Async a -> IO ()
Async.uninterruptibleCancel
{-# INLINEABLE uninterruptibleCancel #-}
cancelWith :: forall e a. (Exception e, HasCallStack) => Async a -> e -> IO ()
cancelWith = Async a -> e -> IO ()
forall e a. Exception e => Async a -> e -> IO ()
Async.cancelWith
{-# INLINEABLE cancelWith #-}
race :: forall a b. HasCallStack => IO a -> IO b -> IO (Either a b)
race = IO a -> IO b -> IO (Either a b)
forall a b. IO a -> IO b -> IO (Either a b)
Async.race
{-# INLINEABLE race #-}
concurrently :: forall a b. HasCallStack => IO a -> IO b -> IO (a, b)
concurrently = IO a -> IO b -> IO (a, b)
forall a b. IO a -> IO b -> IO (a, b)
Async.concurrently
{-# INLINEABLE concurrently #-}
concurrently_ :: forall a b. HasCallStack => IO a -> IO b -> IO ()
concurrently_ = IO a -> IO b -> IO ()
forall a b. IO a -> IO b -> IO ()
Async.concurrently_
{-# INLINEABLE concurrently_ #-}
waitAny :: forall a. HasCallStack => [Async a] -> IO (Async a, a)
waitAny = [Async a] -> IO (Async a, a)
forall a. [Async a] -> IO (Async a, a)
Async.waitAny
{-# INLINEABLE waitAny #-}
waitAnyCatch :: forall a.
HasCallStack =>
[Async a] -> IO (Async a, Either SomeException a)
waitAnyCatch = [Async a] -> IO (Async a, Either SomeException a)
forall a. [Async a] -> IO (Async a, Either SomeException a)
Async.waitAnyCatch
{-# INLINEABLE waitAnyCatch #-}
waitAnyCancel :: forall a. HasCallStack => [Async a] -> IO (Async a, a)
waitAnyCancel = [Async a] -> IO (Async a, a)
forall a. [Async a] -> IO (Async a, a)
Async.waitAnyCancel
{-# INLINEABLE waitAnyCancel #-}
waitAnyCatchCancel :: forall a.
HasCallStack =>
[Async a] -> IO (Async a, Either SomeException a)
waitAnyCatchCancel = [Async a] -> IO (Async a, Either SomeException a)
forall a. [Async a] -> IO (Async a, Either SomeException a)
Async.waitAnyCatchCancel
{-# INLINEABLE waitAnyCatchCancel #-}
waitEither :: forall a b. HasCallStack => Async a -> Async b -> IO (Either a b)
waitEither = Async a -> Async b -> IO (Either a b)
forall a b. Async a -> Async b -> IO (Either a b)
Async.waitEither
{-# INLINEABLE waitEither #-}
waitEitherCatch :: forall a b.
HasCallStack =>
Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b))
waitEitherCatch = Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b))
forall a b.
Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b))
Async.waitEitherCatch
{-# INLINEABLE waitEitherCatch #-}
waitEitherCancel :: forall a b. HasCallStack => Async a -> Async b -> IO (Either a b)
waitEitherCancel = Async a -> Async b -> IO (Either a b)
forall a b. Async a -> Async b -> IO (Either a b)
Async.waitEitherCancel
{-# INLINEABLE waitEitherCancel #-}
waitEitherCatchCancel :: forall a b.
HasCallStack =>
Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b))
waitEitherCatchCancel = Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b))
forall a b.
Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b))
Async.waitEitherCatchCancel
{-# INLINEABLE waitEitherCatchCancel #-}
waitEither_ :: forall a b. HasCallStack => Async a -> Async b -> IO ()
waitEither_ = Async a -> Async b -> IO ()
forall a b. Async a -> Async b -> IO ()
Async.waitEither_
{-# INLINEABLE waitEither_ #-}
waitBoth :: forall a b. HasCallStack => Async a -> Async b -> IO (a, b)
waitBoth = Async a -> Async b -> IO (a, b)
forall a b. Async a -> Async b -> IO (a, b)
Async.waitBoth
{-# INLINEABLE waitBoth #-}
async :: forall a. HasCallStack => IO a -> IO (Async a)
async = IO a -> IO (Async a)
forall a. IO a -> IO (Async a)
Async.async
{-# INLINEABLE async #-}
asyncBound :: forall a. HasCallStack => IO a -> IO (Async a)
asyncBound = IO a -> IO (Async a)
forall a. IO a -> IO (Async a)
Async.asyncBound
{-# INLINEABLE asyncBound #-}
asyncOn :: forall a. HasCallStack => Int -> IO a -> IO (Async a)
asyncOn = Int -> IO a -> IO (Async a)
forall a. Int -> IO a -> IO (Async a)
Async.asyncOn
{-# INLINEABLE asyncOn #-}
asyncWithUnmask :: forall a.
HasCallStack =>
((forall c. IO c -> IO c) -> IO a) -> IO (Async a)
asyncWithUnmask = ((forall c. IO c -> IO c) -> IO a) -> IO (Async a)
forall a. ((forall c. IO c -> IO c) -> IO a) -> IO (Async a)
Async.asyncWithUnmask
{-# INLINEABLE asyncWithUnmask #-}
asyncOnWithUnmask :: forall a.
HasCallStack =>
Int -> ((forall c. IO c -> IO c) -> IO a) -> IO (Async a)
asyncOnWithUnmask = Int -> ((forall c. IO c -> IO c) -> IO a) -> IO (Async a)
forall a. Int -> ((forall c. IO c -> IO c) -> IO a) -> IO (Async a)
Async.asyncOnWithUnmask
{-# INLINEABLE asyncOnWithUnmask #-}
link :: forall a. HasCallStack => Async a -> IO ()
link = Async a -> IO ()
forall a. Async a -> IO ()
Async.link
{-# INLINEABLE link #-}
linkOnly :: forall a.
HasCallStack =>
(SomeException -> Bool) -> Async a -> IO ()
linkOnly = (SomeException -> Bool) -> Async a -> IO ()
forall a. (SomeException -> Bool) -> Async a -> IO ()
Async.linkOnly
{-# INLINEABLE linkOnly #-}
link2 :: forall a b. HasCallStack => Async a -> Async b -> IO ()
link2 = Async a -> Async b -> IO ()
forall a b. Async a -> Async b -> IO ()
Async.link2
{-# INLINEABLE link2 #-}
link2Only :: forall a b.
HasCallStack =>
(SomeException -> Bool) -> Async a -> Async b -> IO ()
link2Only = (SomeException -> Bool) -> Async a -> Async b -> IO ()
forall a b. (SomeException -> Bool) -> Async a -> Async b -> IO ()
Async.link2Only
{-# INLINEABLE link2Only #-}
pooledMapConcurrentlyN :: forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
Positive Int -> (a -> IO b) -> t a -> IO (t b)
pooledMapConcurrentlyN (MkPositive Int
i) =
Int -> (a -> IO b) -> t a -> IO (t b)
forall (m :: * -> *) (t :: * -> *) a b.
(MonadUnliftIO m, Traversable t) =>
Int -> (a -> m b) -> t a -> m (t b)
UAsync.pooledMapConcurrentlyN Int
i
{-# INLINEABLE pooledMapConcurrentlyN #-}
pooledMapConcurrently :: forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
(a -> IO b) -> t a -> IO (t b)
pooledMapConcurrently = (a -> IO b) -> t a -> IO (t b)
forall (m :: * -> *) (t :: * -> *) a b.
(MonadUnliftIO m, Traversable t) =>
(a -> m b) -> t a -> m (t b)
UAsync.pooledMapConcurrently
{-# INLINEABLE pooledMapConcurrently #-}
pooledMapConcurrentlyN_ :: forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
Positive Int -> (a -> IO b) -> f a -> IO ()
pooledMapConcurrentlyN_ (MkPositive Int
i) =
Int -> (a -> IO b) -> f a -> IO ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadUnliftIO m, Foldable f) =>
Int -> (a -> m b) -> f a -> m ()
UAsync.pooledMapConcurrentlyN_ Int
i
{-# INLINEABLE pooledMapConcurrentlyN_ #-}
pooledMapConcurrently_ :: forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
(a -> IO b) -> f a -> IO ()
pooledMapConcurrently_ = (a -> IO b) -> f a -> IO ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadUnliftIO m, Foldable f) =>
(a -> m b) -> f a -> m ()
UAsync.pooledMapConcurrently_
{-# INLINEABLE pooledMapConcurrently_ #-}
instance (MonadAsync m) => MonadAsync (ReaderT env m) where
withAsync :: forall a b.
HasCallStack =>
ReaderT env m a -> (Async a -> ReaderT env m b) -> ReaderT env m b
withAsync ReaderT env m a
rdr Async a -> ReaderT env m b
onAsync =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m b) -> ReaderT env m b
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m b -> ReaderT env m b
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> ReaderT env m b) -> m b -> ReaderT env m b
forall a b. (a -> b) -> a -> b
$ m a -> (Async a -> m b) -> m b
forall a b. HasCallStack => m a -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> (Async a -> m b) -> m b
withAsync (ReaderT env m a -> env -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m a
rdr env
e) ((Async a -> m b) -> m b) -> (Async a -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ \Async a
a -> env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (Async a -> ReaderT env m b
onAsync Async a
a)
{-# INLINEABLE withAsync #-}
withAsyncBound :: forall a b.
HasCallStack =>
ReaderT env m a -> (Async a -> ReaderT env m b) -> ReaderT env m b
withAsyncBound ReaderT env m a
rdr Async a -> ReaderT env m b
onAsync =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m b) -> ReaderT env m b
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m b -> ReaderT env m b
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> ReaderT env m b) -> m b -> ReaderT env m b
forall a b. (a -> b) -> a -> b
$ m a -> (Async a -> m b) -> m b
forall a b. HasCallStack => m a -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> (Async a -> m b) -> m b
withAsyncBound (ReaderT env m a -> env -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m a
rdr env
e) ((Async a -> m b) -> m b) -> (Async a -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ \Async a
a -> env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (Async a -> ReaderT env m b
onAsync Async a
a)
{-# INLINEABLE withAsyncBound #-}
withAsyncOn :: forall a b.
HasCallStack =>
Int
-> ReaderT env m a
-> (Async a -> ReaderT env m b)
-> ReaderT env m b
withAsyncOn Int
i ReaderT env m a
rdr Async a -> ReaderT env m b
onAsync =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m b) -> ReaderT env m b
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m b -> ReaderT env m b
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> ReaderT env m b) -> m b -> ReaderT env m b
forall a b. (a -> b) -> a -> b
$ Int -> m a -> (Async a -> m b) -> m b
forall a b. HasCallStack => Int -> m a -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Int -> m a -> (Async a -> m b) -> m b
withAsyncOn Int
i (ReaderT env m a -> env -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m a
rdr env
e) ((Async a -> m b) -> m b) -> (Async a -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m b -> m b)
-> (Async a -> ReaderT env m b) -> Async a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> ReaderT env m b
onAsync
{-# INLINEABLE withAsyncOn #-}
withAsyncWithUnmask :: forall a b.
HasCallStack =>
((forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a)
-> (Async a -> ReaderT env m b) -> ReaderT env m b
withAsyncWithUnmask (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m Async a -> ReaderT env m b
onAsync =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m b) -> ReaderT env m b
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m b -> ReaderT env m b
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> ReaderT env m b) -> m b -> ReaderT env m b
forall a b. (a -> b) -> a -> b
$
((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
forall a b.
HasCallStack =>
((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
withAsyncWithUnmask
(\forall c. m c -> m c
unmask -> env -> ReaderT env m a -> m a
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m a -> m a) -> ReaderT env m a -> m a
forall a b. (a -> b) -> a -> b
$ (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m ((forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a)
-> (forall c. ReaderT env m c -> ReaderT env m c)
-> ReaderT env m a
forall a b. (a -> b) -> a -> b
$ \ReaderT env m c
r -> m c -> ReaderT env m c
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m c -> m c
forall c. m c -> m c
unmask (ReaderT env m c -> env -> m c
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m c
r env
e)))
(env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m b -> m b)
-> (Async a -> ReaderT env m b) -> Async a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> ReaderT env m b
onAsync)
{-# INLINEABLE withAsyncWithUnmask #-}
withAsyncOnWithUnmask :: forall a b.
HasCallStack =>
Int
-> ((forall c. ReaderT env m c -> ReaderT env m c)
-> ReaderT env m a)
-> (Async a -> ReaderT env m b)
-> ReaderT env m b
withAsyncOnWithUnmask Int
i (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m Async a -> ReaderT env m b
onAsync =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m b) -> ReaderT env m b
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m b -> ReaderT env m b
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> ReaderT env m b) -> m b -> ReaderT env m b
forall a b. (a -> b) -> a -> b
$
Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
forall a b.
HasCallStack =>
Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
withAsyncOnWithUnmask
Int
i
(\forall c. m c -> m c
unmask -> env -> ReaderT env m a -> m a
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m a -> m a) -> ReaderT env m a -> m a
forall a b. (a -> b) -> a -> b
$ (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m ((forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a)
-> (forall c. ReaderT env m c -> ReaderT env m c)
-> ReaderT env m a
forall a b. (a -> b) -> a -> b
$ \ReaderT env m c
r -> m c -> ReaderT env m c
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m c -> m c
forall c. m c -> m c
unmask (ReaderT env m c -> env -> m c
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m c
r env
e)))
(env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m b -> m b)
-> (Async a -> ReaderT env m b) -> Async a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> ReaderT env m b
onAsync)
{-# INLINEABLE withAsyncOnWithUnmask #-}
wait :: forall a. HasCallStack => Async a -> ReaderT env m a
wait = m a -> ReaderT env m a
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ReaderT env m a)
-> (Async a -> m a) -> Async a -> ReaderT env m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> m a
forall a. HasCallStack => Async a -> m a
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Async a -> m a
wait
{-# INLINEABLE wait #-}
poll :: forall a.
HasCallStack =>
Async a -> ReaderT env m (Maybe (Either SomeException a))
poll = m (Maybe (Either SomeException a))
-> ReaderT env m (Maybe (Either SomeException a))
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Maybe (Either SomeException a))
-> ReaderT env m (Maybe (Either SomeException a)))
-> (Async a -> m (Maybe (Either SomeException a)))
-> Async a
-> ReaderT env m (Maybe (Either SomeException a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> m (Maybe (Either SomeException a))
forall a.
HasCallStack =>
Async a -> m (Maybe (Either SomeException a))
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Async a -> m (Maybe (Either SomeException a))
poll
{-# INLINEABLE poll #-}
waitCatch :: forall a.
HasCallStack =>
Async a -> ReaderT env m (Either SomeException a)
waitCatch = m (Either SomeException a)
-> ReaderT env m (Either SomeException a)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either SomeException a)
-> ReaderT env m (Either SomeException a))
-> (Async a -> m (Either SomeException a))
-> Async a
-> ReaderT env m (Either SomeException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> m (Either SomeException a)
forall a. HasCallStack => Async a -> m (Either SomeException a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Async a -> m (Either SomeException a)
waitCatch
{-# INLINEABLE waitCatch #-}
cancel :: forall a. HasCallStack => Async a -> ReaderT env m ()
cancel = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ())
-> (Async a -> m ()) -> Async a -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> m ()
forall a. HasCallStack => Async a -> m ()
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Async a -> m ()
cancel
{-# INLINEABLE cancel #-}
uninterruptibleCancel :: forall a. HasCallStack => Async a -> ReaderT env m ()
uninterruptibleCancel = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ())
-> (Async a -> m ()) -> Async a -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> m ()
forall a. HasCallStack => Async a -> m ()
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Async a -> m ()
uninterruptibleCancel
{-# INLINEABLE uninterruptibleCancel #-}
cancelWith :: forall e a.
(Exception e, HasCallStack) =>
Async a -> e -> ReaderT env m ()
cancelWith Async a
x = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ()) -> (e -> m ()) -> e -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> e -> m ()
forall e a. (Exception e, HasCallStack) => Async a -> e -> m ()
forall (m :: * -> *) e a.
(MonadAsync m, Exception e, HasCallStack) =>
Async a -> e -> m ()
cancelWith Async a
x
{-# INLINEABLE cancelWith #-}
race :: forall a b.
HasCallStack =>
ReaderT env m a -> ReaderT env m b -> ReaderT env m (Either a b)
race ReaderT env m a
left ReaderT env m b
right =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env
-> (env -> ReaderT env m (Either a b))
-> ReaderT env m (Either a b)
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
let left' :: m a
left' = ReaderT env m a -> env -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m a
left env
e
right' :: m b
right' = ReaderT env m b -> env -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m b
right env
e
in m (Either a b) -> ReaderT env m (Either a b)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either a b) -> ReaderT env m (Either a b))
-> m (Either a b) -> ReaderT env m (Either a b)
forall a b. (a -> b) -> a -> b
$ m a -> m b -> m (Either a b)
forall a b. HasCallStack => m a -> m b -> m (Either a b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> m b -> m (Either a b)
race m a
left' m b
right'
{-# INLINEABLE race #-}
concurrently :: forall a b.
HasCallStack =>
ReaderT env m a -> ReaderT env m b -> ReaderT env m (a, b)
concurrently ReaderT env m a
left ReaderT env m b
right =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env
-> (env -> ReaderT env m (a, b)) -> ReaderT env m (a, b)
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
let left' :: m a
left' = ReaderT env m a -> env -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m a
left env
e
right' :: m b
right' = ReaderT env m b -> env -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m b
right env
e
in m (a, b) -> ReaderT env m (a, b)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, b) -> ReaderT env m (a, b))
-> m (a, b) -> ReaderT env m (a, b)
forall a b. (a -> b) -> a -> b
$ m a -> m b -> m (a, b)
forall a b. HasCallStack => m a -> m b -> m (a, b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> m b -> m (a, b)
concurrently m a
left' m b
right'
{-# INLINEABLE concurrently #-}
concurrently_ :: forall a b.
HasCallStack =>
ReaderT env m a -> ReaderT env m b -> ReaderT env m ()
concurrently_ ReaderT env m a
left ReaderT env m b
right =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m ()) -> ReaderT env m ()
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
let left' :: m a
left' = ReaderT env m a -> env -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m a
left env
e
right' :: m b
right' = ReaderT env m b -> env -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m b
right env
e
in m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ()) -> m () -> ReaderT env m ()
forall a b. (a -> b) -> a -> b
$ m a -> m b -> m ()
forall a b. HasCallStack => m a -> m b -> m ()
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> m b -> m ()
concurrently_ m a
left' m b
right'
{-# INLINEABLE concurrently_ #-}
waitAny :: forall a. HasCallStack => [Async a] -> ReaderT env m (Async a, a)
waitAny = m (Async a, a) -> ReaderT env m (Async a, a)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Async a, a) -> ReaderT env m (Async a, a))
-> ([Async a] -> m (Async a, a))
-> [Async a]
-> ReaderT env m (Async a, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> m (Async a, a)
forall a. HasCallStack => [Async a] -> m (Async a, a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
[Async a] -> m (Async a, a)
waitAny
{-# INLINEABLE waitAny #-}
waitAnyCatch :: forall a.
HasCallStack =>
[Async a] -> ReaderT env m (Async a, Either SomeException a)
waitAnyCatch = m (Async a, Either SomeException a)
-> ReaderT env m (Async a, Either SomeException a)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Async a, Either SomeException a)
-> ReaderT env m (Async a, Either SomeException a))
-> ([Async a] -> m (Async a, Either SomeException a))
-> [Async a]
-> ReaderT env m (Async a, Either SomeException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> m (Async a, Either SomeException a)
forall a.
HasCallStack =>
[Async a] -> m (Async a, Either SomeException a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
[Async a] -> m (Async a, Either SomeException a)
waitAnyCatch
{-# INLINEABLE waitAnyCatch #-}
waitAnyCancel :: forall a. HasCallStack => [Async a] -> ReaderT env m (Async a, a)
waitAnyCancel = m (Async a, a) -> ReaderT env m (Async a, a)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Async a, a) -> ReaderT env m (Async a, a))
-> ([Async a] -> m (Async a, a))
-> [Async a]
-> ReaderT env m (Async a, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> m (Async a, a)
forall a. HasCallStack => [Async a] -> m (Async a, a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
[Async a] -> m (Async a, a)
waitAnyCancel
{-# INLINEABLE waitAnyCancel #-}
waitAnyCatchCancel :: forall a.
HasCallStack =>
[Async a] -> ReaderT env m (Async a, Either SomeException a)
waitAnyCatchCancel = m (Async a, Either SomeException a)
-> ReaderT env m (Async a, Either SomeException a)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Async a, Either SomeException a)
-> ReaderT env m (Async a, Either SomeException a))
-> ([Async a] -> m (Async a, Either SomeException a))
-> [Async a]
-> ReaderT env m (Async a, Either SomeException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> m (Async a, Either SomeException a)
forall a.
HasCallStack =>
[Async a] -> m (Async a, Either SomeException a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
[Async a] -> m (Async a, Either SomeException a)
waitAnyCatchCancel
{-# INLINEABLE waitAnyCatchCancel #-}
waitEither :: forall a b.
HasCallStack =>
Async a -> Async b -> ReaderT env m (Either a b)
waitEither Async a
x = m (Either a b) -> ReaderT env m (Either a b)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either a b) -> ReaderT env m (Either a b))
-> (Async b -> m (Either a b))
-> Async b
-> ReaderT env m (Either a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> m (Either a b)
forall a b. HasCallStack => Async a -> Async b -> m (Either a b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Async a -> Async b -> m (Either a b)
waitEither Async a
x
{-# INLINEABLE waitEither #-}
waitEitherCatch :: forall a b.
HasCallStack =>
Async a
-> Async b
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatch Async a
x = m (Either (Either SomeException a) (Either SomeException b))
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b))
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either (Either SomeException a) (Either SomeException b))
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b)))
-> (Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> Async b
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall a b.
HasCallStack =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatch Async a
x
{-# INLINEABLE waitEitherCatch #-}
waitEitherCancel :: forall a b.
HasCallStack =>
Async a -> Async b -> ReaderT env m (Either a b)
waitEitherCancel Async a
x = m (Either a b) -> ReaderT env m (Either a b)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either a b) -> ReaderT env m (Either a b))
-> (Async b -> m (Either a b))
-> Async b
-> ReaderT env m (Either a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> m (Either a b)
forall a b. HasCallStack => Async a -> Async b -> m (Either a b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Async a -> Async b -> m (Either a b)
waitEitherCancel Async a
x
{-# INLINEABLE waitEitherCancel #-}
waitEitherCatchCancel :: forall a b.
HasCallStack =>
Async a
-> Async b
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatchCancel Async a
x = m (Either (Either SomeException a) (Either SomeException b))
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b))
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either (Either SomeException a) (Either SomeException b))
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b)))
-> (Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> Async b
-> ReaderT
env m (Either (Either SomeException a) (Either SomeException b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall a b.
HasCallStack =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatchCancel Async a
x
{-# INLINEABLE waitEitherCatchCancel #-}
waitEither_ :: forall a b. HasCallStack => Async a -> Async b -> ReaderT env m ()
waitEither_ Async a
x = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ())
-> (Async b -> m ()) -> Async b -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> m ()
forall a b. HasCallStack => Async a -> Async b -> m ()
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Async a -> Async b -> m ()
waitEither_ Async a
x
{-# INLINEABLE waitEither_ #-}
waitBoth :: forall a b.
HasCallStack =>
Async a -> Async b -> ReaderT env m (a, b)
waitBoth Async a
x = m (a, b) -> ReaderT env m (a, b)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (a, b) -> ReaderT env m (a, b))
-> (Async b -> m (a, b)) -> Async b -> ReaderT env m (a, b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> m (a, b)
forall a b. HasCallStack => Async a -> Async b -> m (a, b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Async a -> Async b -> m (a, b)
waitBoth Async a
x
{-# INLINEABLE waitBoth #-}
async :: forall a.
HasCallStack =>
ReaderT env m a -> ReaderT env m (Async a)
async = (m a -> m (Async a)) -> ReaderT env m a -> ReaderT env m (Async a)
forall (m :: * -> *) a (n :: * -> *) b r.
(m a -> n b) -> ReaderT r m a -> ReaderT r n b
mapReaderT m a -> m (Async a)
forall a. HasCallStack => m a -> m (Async a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
m a -> m (Async a)
async
{-# INLINEABLE async #-}
asyncBound :: forall a.
HasCallStack =>
ReaderT env m a -> ReaderT env m (Async a)
asyncBound = (m a -> m (Async a)) -> ReaderT env m a -> ReaderT env m (Async a)
forall (m :: * -> *) a (n :: * -> *) b r.
(m a -> n b) -> ReaderT r m a -> ReaderT r n b
mapReaderT m a -> m (Async a)
forall a. HasCallStack => m a -> m (Async a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
m a -> m (Async a)
asyncBound
{-# INLINEABLE asyncBound #-}
asyncOn :: forall a.
HasCallStack =>
Int -> ReaderT env m a -> ReaderT env m (Async a)
asyncOn Int
i = (m a -> m (Async a)) -> ReaderT env m a -> ReaderT env m (Async a)
forall (m :: * -> *) a (n :: * -> *) b r.
(m a -> n b) -> ReaderT r m a -> ReaderT r n b
mapReaderT ((m a -> m (Async a))
-> ReaderT env m a -> ReaderT env m (Async a))
-> (m a -> m (Async a))
-> ReaderT env m a
-> ReaderT env m (Async a)
forall a b. (a -> b) -> a -> b
$ Int -> m a -> m (Async a)
forall a. HasCallStack => Int -> m a -> m (Async a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Int -> m a -> m (Async a)
asyncOn Int
i
{-# INLINEABLE asyncOn #-}
asyncWithUnmask :: forall a.
HasCallStack =>
((forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a)
-> ReaderT env m (Async a)
asyncWithUnmask (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env
-> (env -> ReaderT env m (Async a)) -> ReaderT env m (Async a)
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m (Async a) -> ReaderT env m (Async a)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Async a) -> ReaderT env m (Async a))
-> m (Async a) -> ReaderT env m (Async a)
forall a b. (a -> b) -> a -> b
$ ((forall c. m c -> m c) -> m a) -> m (Async a)
forall a.
HasCallStack =>
((forall c. m c -> m c) -> m a) -> m (Async a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
((forall c. m c -> m c) -> m a) -> m (Async a)
asyncWithUnmask (((forall c. m c -> m c) -> m a) -> m (Async a))
-> ((forall c. m c -> m c) -> m a) -> m (Async a)
forall a b. (a -> b) -> a -> b
$ \forall c. m c -> m c
unmask ->
env -> ReaderT env m a -> m a
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m a -> m a) -> ReaderT env m a -> m a
forall a b. (a -> b) -> a -> b
$ (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m ((forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a)
-> (forall c. ReaderT env m c -> ReaderT env m c)
-> ReaderT env m a
forall a b. (a -> b) -> a -> b
$ \ReaderT env m b
r -> m b -> ReaderT env m b
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> m b
forall c. m c -> m c
unmask (ReaderT env m b -> env -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m b
r env
e))
{-# INLINEABLE asyncWithUnmask #-}
asyncOnWithUnmask :: forall a.
HasCallStack =>
Int
-> ((forall c. ReaderT env m c -> ReaderT env m c)
-> ReaderT env m a)
-> ReaderT env m (Async a)
asyncOnWithUnmask Int
i (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env
-> (env -> ReaderT env m (Async a)) -> ReaderT env m (Async a)
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m (Async a) -> ReaderT env m (Async a)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Async a) -> ReaderT env m (Async a))
-> m (Async a) -> ReaderT env m (Async a)
forall a b. (a -> b) -> a -> b
$ Int -> ((forall c. m c -> m c) -> m a) -> m (Async a)
forall a.
HasCallStack =>
Int -> ((forall c. m c -> m c) -> m a) -> m (Async a)
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Int -> ((forall c. m c -> m c) -> m a) -> m (Async a)
asyncOnWithUnmask Int
i (((forall c. m c -> m c) -> m a) -> m (Async a))
-> ((forall c. m c -> m c) -> m a) -> m (Async a)
forall a b. (a -> b) -> a -> b
$ \forall c. m c -> m c
unmask ->
env -> ReaderT env m a -> m a
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m a -> m a) -> ReaderT env m a -> m a
forall a b. (a -> b) -> a -> b
$ (forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a
m ((forall c. ReaderT env m c -> ReaderT env m c) -> ReaderT env m a)
-> (forall c. ReaderT env m c -> ReaderT env m c)
-> ReaderT env m a
forall a b. (a -> b) -> a -> b
$ \ReaderT env m b
r -> m b -> ReaderT env m b
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m b -> m b
forall c. m c -> m c
unmask (ReaderT env m b -> env -> m b
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT env m b
r env
e))
{-# INLINEABLE asyncOnWithUnmask #-}
link :: forall a. HasCallStack => Async a -> ReaderT env m ()
link = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ())
-> (Async a -> m ()) -> Async a -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> m ()
forall a. HasCallStack => Async a -> m ()
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
Async a -> m ()
link
{-# INLINEABLE link #-}
linkOnly :: forall a.
HasCallStack =>
(SomeException -> Bool) -> Async a -> ReaderT env m ()
linkOnly SomeException -> Bool
f = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ())
-> (Async a -> m ()) -> Async a -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SomeException -> Bool) -> Async a -> m ()
forall a.
HasCallStack =>
(SomeException -> Bool) -> Async a -> m ()
forall (m :: * -> *) a.
(MonadAsync m, HasCallStack) =>
(SomeException -> Bool) -> Async a -> m ()
linkOnly SomeException -> Bool
f
{-# INLINEABLE linkOnly #-}
link2 :: forall a b. HasCallStack => Async a -> Async b -> ReaderT env m ()
link2 Async a
x = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ())
-> (Async b -> m ()) -> Async b -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> m ()
forall a b. HasCallStack => Async a -> Async b -> m ()
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
Async a -> Async b -> m ()
link2 Async a
x
{-# INLINEABLE link2 #-}
link2Only :: forall a b.
HasCallStack =>
(SomeException -> Bool) -> Async a -> Async b -> ReaderT env m ()
link2Only SomeException -> Bool
f Async a
x = m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ())
-> (Async b -> m ()) -> Async b -> ReaderT env m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SomeException -> Bool) -> Async a -> Async b -> m ()
forall a b.
HasCallStack =>
(SomeException -> Bool) -> Async a -> Async b -> m ()
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
(SomeException -> Bool) -> Async a -> Async b -> m ()
link2Only SomeException -> Bool
f Async a
x
{-# INLINEABLE link2Only #-}
pooledMapConcurrentlyN :: forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
Positive Int
-> (a -> ReaderT env m b) -> t a -> ReaderT env m (t b)
pooledMapConcurrentlyN Positive Int
i a -> ReaderT env m b
f t a
xs =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env
-> (env -> ReaderT env m (t b)) -> ReaderT env m (t b)
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m (t b) -> ReaderT env m (t b)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (t b) -> ReaderT env m (t b)) -> m (t b) -> ReaderT env m (t b)
forall a b. (a -> b) -> a -> b
$ Positive Int -> (a -> m b) -> t a -> m (t b)
forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, HasCallStack, Traversable t) =>
Positive Int -> (a -> m b) -> t a -> m (t b)
forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
Positive Int -> (a -> m b) -> t a -> m (t b)
pooledMapConcurrentlyN Positive Int
i (env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m b -> m b) -> (a -> ReaderT env m b) -> a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ReaderT env m b
f) t a
xs
{-# INLINEABLE pooledMapConcurrentlyN #-}
pooledMapConcurrently :: forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
(a -> ReaderT env m b) -> t a -> ReaderT env m (t b)
pooledMapConcurrently a -> ReaderT env m b
f t a
xs =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env
-> (env -> ReaderT env m (t b)) -> ReaderT env m (t b)
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m (t b) -> ReaderT env m (t b)
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (t b) -> ReaderT env m (t b)) -> m (t b) -> ReaderT env m (t b)
forall a b. (a -> b) -> a -> b
$ (a -> m b) -> t a -> m (t b)
forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, HasCallStack, Traversable t) =>
(a -> m b) -> t a -> m (t b)
forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
(a -> m b) -> t a -> m (t b)
pooledMapConcurrently (env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m b -> m b) -> (a -> ReaderT env m b) -> a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ReaderT env m b
f) t a
xs
{-# INLINEABLE pooledMapConcurrently #-}
pooledMapConcurrentlyN_ :: forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
Positive Int -> (a -> ReaderT env m b) -> f a -> ReaderT env m ()
pooledMapConcurrentlyN_ Positive Int
i a -> ReaderT env m b
f f a
xs =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m ()) -> ReaderT env m ()
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ()) -> m () -> ReaderT env m ()
forall a b. (a -> b) -> a -> b
$ Positive Int -> (a -> m b) -> f a -> m ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f, HasCallStack) =>
Positive Int -> (a -> m b) -> f a -> m ()
forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
Positive Int -> (a -> m b) -> f a -> m ()
pooledMapConcurrentlyN_ Positive Int
i (env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m b -> m b) -> (a -> ReaderT env m b) -> a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ReaderT env m b
f) f a
xs
{-# INLINEABLE pooledMapConcurrentlyN_ #-}
pooledMapConcurrently_ :: forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
(a -> ReaderT env m b) -> f a -> ReaderT env m ()
pooledMapConcurrently_ a -> ReaderT env m b
f f a
xs =
ReaderT env m env
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask ReaderT env m env -> (env -> ReaderT env m ()) -> ReaderT env m ()
forall a b.
ReaderT env m a -> (a -> ReaderT env m b) -> ReaderT env m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \env
e ->
m () -> ReaderT env m ()
forall (m :: * -> *) a. Monad m => m a -> ReaderT env m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT env m ()) -> m () -> ReaderT env m ()
forall a b. (a -> b) -> a -> b
$ (a -> m b) -> f a -> m ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f, HasCallStack) =>
(a -> m b) -> f a -> m ()
forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
(a -> m b) -> f a -> m ()
pooledMapConcurrently_ (env -> ReaderT env m b -> m b
forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT env
e (ReaderT env m b -> m b) -> (a -> ReaderT env m b) -> a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ReaderT env m b
f) f a
xs
{-# INLINEABLE pooledMapConcurrently_ #-}
usingReaderT :: forall m env a. env -> ReaderT env m a -> m a
usingReaderT :: forall (m :: * -> *) env a. env -> ReaderT env m a -> m a
usingReaderT = (ReaderT env m a -> env -> m a) -> env -> ReaderT env m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT env m a -> env -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT
{-# INLINEABLE usingReaderT #-}
race_ :: forall m a b. (HasCallStack, MonadAsync m) => m a -> m b -> m ()
race_ :: forall (m :: * -> *) a b.
(HasCallStack, MonadAsync m) =>
m a -> m b -> m ()
race_ m a
left = m (Either a b) -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m (Either a b) -> m ()) -> (m b -> m (Either a b)) -> m b -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> m b -> m (Either a b)
forall a b. HasCallStack => m a -> m b -> m (Either a b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> m b -> m (Either a b)
race m a
left
{-# INLINEABLE race_ #-}
newtype Concurrently m a = Concurrently
{
forall {k} (m :: k -> *) (a :: k). Concurrently m a -> m a
runConcurrently :: m a
}
instance (Functor m) => Functor (Concurrently m) where
fmap :: forall a b. (a -> b) -> Concurrently m a -> Concurrently m b
fmap a -> b
f (Concurrently m a
a) = m b -> Concurrently m b
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m b -> Concurrently m b) -> m b -> Concurrently m b
forall a b. (a -> b) -> a -> b
$ a -> b
f (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m a
a
instance (MonadAsync m) => Applicative (Concurrently m) where
pure :: forall a. a -> Concurrently m a
pure = m a -> Concurrently m a
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m a -> Concurrently m a) -> (a -> m a) -> a -> Concurrently m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> m a
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Concurrently m (a -> b)
fs <*> :: forall a b.
Concurrently m (a -> b) -> Concurrently m a -> Concurrently m b
<*> Concurrently m a
as =
m b -> Concurrently m b
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m b -> Concurrently m b) -> m b -> Concurrently m b
forall a b. (a -> b) -> a -> b
$ (\(a -> b
f, a
a) -> a -> b
f a
a) ((a -> b, a) -> b) -> m (a -> b, a) -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (a -> b) -> m a -> m (a -> b, a)
forall a b. HasCallStack => m a -> m b -> m (a, b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> m b -> m (a, b)
concurrently m (a -> b)
fs m a
as
instance (MonadAsync m, MonadThread m) => Alternative (Concurrently m) where
empty :: forall a. Concurrently m a
empty = m a -> Concurrently m a
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m a -> Concurrently m a) -> m a -> Concurrently m a
forall a b. (a -> b) -> a -> b
$ m () -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (Int -> m ()
forall (m :: * -> *). (MonadThread m, HasCallStack) => Int -> m ()
threadDelay Int
forall a. Bounded a => a
maxBound)
Concurrently m a
as <|> :: forall a. Concurrently m a -> Concurrently m a -> Concurrently m a
<|> Concurrently m a
bs =
m a -> Concurrently m a
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m a -> Concurrently m a) -> m a -> Concurrently m a
forall a b. (a -> b) -> a -> b
$ (a -> a) -> (a -> a) -> Either a a -> a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> a
forall a. a -> a
id a -> a
forall a. a -> a
id (Either a a -> a) -> m (Either a a) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m a -> m a -> m (Either a a)
forall a b. HasCallStack => m a -> m b -> m (Either a b)
forall (m :: * -> *) a b.
(MonadAsync m, HasCallStack) =>
m a -> m b -> m (Either a b)
race m a
as m a
bs
instance (MonadAsync m, Semigroup a) => Semigroup (Concurrently m a) where
<> :: Concurrently m a -> Concurrently m a -> Concurrently m a
(<>) = (a -> a -> a)
-> Concurrently m a -> Concurrently m a -> Concurrently m a
forall a b c.
(a -> b -> c)
-> Concurrently m a -> Concurrently m b -> Concurrently m c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)
instance (MonadAsync m, Monoid a) => Monoid (Concurrently m a) where
mempty :: Concurrently m a
mempty = a -> Concurrently m a
forall a. a -> Concurrently m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
mappend :: Concurrently m a -> Concurrently m a -> Concurrently m a
mappend = Concurrently m a -> Concurrently m a -> Concurrently m a
forall a. Semigroup a => a -> a -> a
(<>)
mapConcurrently ::
forall m t a b.
( MonadAsync m,
Traversable t
) =>
(a -> m b) ->
t a ->
m (t b)
mapConcurrently :: forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, Traversable t) =>
(a -> m b) -> t a -> m (t b)
mapConcurrently a -> m b
f = Concurrently m (t b) -> m (t b)
forall {k} (m :: k -> *) (a :: k). Concurrently m a -> m a
runConcurrently (Concurrently m (t b) -> m (t b))
-> (t a -> Concurrently m (t b)) -> t a -> m (t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Concurrently m b) -> t a -> Concurrently m (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
traverse (m b -> Concurrently m b
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m b -> Concurrently m b) -> (a -> m b) -> a -> Concurrently m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> m b
f)
{-# INLINEABLE mapConcurrently #-}
forConcurrently ::
forall m t a b.
( MonadAsync m,
Traversable t
) =>
t a ->
(a -> m b) ->
m (t b)
forConcurrently :: forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, Traversable t) =>
t a -> (a -> m b) -> m (t b)
forConcurrently = ((a -> m b) -> t a -> m (t b)) -> t a -> (a -> m b) -> m (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> m b) -> t a -> m (t b)
forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, Traversable t) =>
(a -> m b) -> t a -> m (t b)
mapConcurrently
{-# INLINEABLE forConcurrently #-}
mapConcurrently_ ::
forall m f a b.
( MonadAsync m,
Foldable f
) =>
(a -> m b) ->
f a ->
m ()
mapConcurrently_ :: forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f) =>
(a -> m b) -> f a -> m ()
mapConcurrently_ a -> m b
f = Concurrently m () -> m ()
forall {k} (m :: k -> *) (a :: k). Concurrently m a -> m a
runConcurrently (Concurrently m () -> m ())
-> (f a -> Concurrently m ()) -> f a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Concurrently m ()) -> f a -> Concurrently m ()
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (m () -> Concurrently m ()
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m () -> Concurrently m ())
-> (a -> m ()) -> a -> Concurrently m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m b -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m b -> m ()) -> (a -> m b) -> a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> m b
f)
{-# INLINEABLE mapConcurrently_ #-}
forConcurrently_ ::
forall m f a b.
( MonadAsync m,
Foldable f
) =>
f a ->
(a -> m b) ->
m ()
forConcurrently_ :: forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f) =>
f a -> (a -> m b) -> m ()
forConcurrently_ = ((a -> m b) -> f a -> m ()) -> f a -> (a -> m b) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> m b) -> f a -> m ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f) =>
(a -> m b) -> f a -> m ()
mapConcurrently_
{-# INLINEABLE forConcurrently_ #-}
replicateConcurrently :: forall m a. (MonadAsync m) => Int -> m a -> m [a]
replicateConcurrently :: forall (m :: * -> *) a. MonadAsync m => Int -> m a -> m [a]
replicateConcurrently Int
cnt = Concurrently m [a] -> m [a]
forall {k} (m :: k -> *) (a :: k). Concurrently m a -> m a
runConcurrently (Concurrently m [a] -> m [a])
-> (m a -> Concurrently m [a]) -> m a -> m [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Concurrently m a -> Concurrently m [a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
cnt (Concurrently m a -> Concurrently m [a])
-> (m a -> Concurrently m a) -> m a -> Concurrently m [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> Concurrently m a
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently
{-# INLINEABLE replicateConcurrently #-}
replicateConcurrently_ :: forall m a. (MonadAsync m) => Int -> m a -> m ()
replicateConcurrently_ :: forall (m :: * -> *) a. MonadAsync m => Int -> m a -> m ()
replicateConcurrently_ Int
cnt =
Concurrently m () -> m ()
forall {k} (m :: k -> *) (a :: k). Concurrently m a -> m a
runConcurrently (Concurrently m () -> m ())
-> (m a -> Concurrently m ()) -> m a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Concurrently m ()] -> Concurrently m ()
forall m. Monoid m => [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ([Concurrently m ()] -> Concurrently m ())
-> (m a -> [Concurrently m ()]) -> m a -> Concurrently m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Concurrently m () -> [Concurrently m ()]
forall a. Int -> a -> [a]
replicate Int
cnt (Concurrently m () -> [Concurrently m ()])
-> (m a -> Concurrently m ()) -> m a -> [Concurrently m ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m () -> Concurrently m ()
forall {k} (m :: k -> *) (a :: k). m a -> Concurrently m a
Concurrently (m () -> Concurrently m ())
-> (m a -> m ()) -> m a -> Concurrently m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
{-# INLINEABLE replicateConcurrently_ #-}
pooledForConcurrentlyN ::
forall m t a b.
( HasCallStack,
MonadAsync m,
Traversable t
) =>
Positive Int ->
t a ->
(a -> m b) ->
m (t b)
pooledForConcurrentlyN :: forall (m :: * -> *) (t :: * -> *) a b.
(HasCallStack, MonadAsync m, Traversable t) =>
Positive Int -> t a -> (a -> m b) -> m (t b)
pooledForConcurrentlyN Positive Int
numProcs = ((a -> m b) -> t a -> m (t b)) -> t a -> (a -> m b) -> m (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Positive Int -> (a -> m b) -> t a -> m (t b)
forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, HasCallStack, Traversable t) =>
Positive Int -> (a -> m b) -> t a -> m (t b)
forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
Positive Int -> (a -> m b) -> t a -> m (t b)
pooledMapConcurrentlyN Positive Int
numProcs)
{-# INLINEABLE pooledForConcurrentlyN #-}
pooledForConcurrently ::
forall m t a b.
( HasCallStack,
MonadAsync m,
Traversable t
) =>
t a ->
(a -> m b) ->
m (t b)
pooledForConcurrently :: forall (m :: * -> *) (t :: * -> *) a b.
(HasCallStack, MonadAsync m, Traversable t) =>
t a -> (a -> m b) -> m (t b)
pooledForConcurrently = ((a -> m b) -> t a -> m (t b)) -> t a -> (a -> m b) -> m (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> m b) -> t a -> m (t b)
forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, HasCallStack, Traversable t) =>
(a -> m b) -> t a -> m (t b)
forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
(a -> m b) -> t a -> m (t b)
pooledMapConcurrently
{-# INLINEABLE pooledForConcurrently #-}
pooledForConcurrentlyN_ ::
forall m f a b.
( Foldable f,
HasCallStack,
MonadAsync m
) =>
Positive Int ->
f a ->
(a -> m b) ->
m ()
pooledForConcurrentlyN_ :: forall (m :: * -> *) (f :: * -> *) a b.
(Foldable f, HasCallStack, MonadAsync m) =>
Positive Int -> f a -> (a -> m b) -> m ()
pooledForConcurrentlyN_ Positive Int
numProcs = ((a -> m b) -> f a -> m ()) -> f a -> (a -> m b) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Positive Int -> (a -> m b) -> f a -> m ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f, HasCallStack) =>
Positive Int -> (a -> m b) -> f a -> m ()
forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
Positive Int -> (a -> m b) -> f a -> m ()
pooledMapConcurrentlyN_ Positive Int
numProcs)
{-# INLINEABLE pooledForConcurrentlyN_ #-}
pooledForConcurrently_ ::
forall m f a b.
( Foldable f,
HasCallStack,
MonadAsync m
) =>
f a ->
(a -> m b) ->
m ()
pooledForConcurrently_ :: forall (m :: * -> *) (f :: * -> *) a b.
(Foldable f, HasCallStack, MonadAsync m) =>
f a -> (a -> m b) -> m ()
pooledForConcurrently_ = ((a -> m b) -> f a -> m ()) -> f a -> (a -> m b) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> m b) -> f a -> m ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f, HasCallStack) =>
(a -> m b) -> f a -> m ()
forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
(a -> m b) -> f a -> m ()
pooledMapConcurrently_
{-# INLINEABLE pooledForConcurrently_ #-}
pooledReplicateConcurrentlyN ::
forall m a.
( HasCallStack,
MonadAsync m
) =>
Positive Int ->
Int ->
m a ->
m [a]
pooledReplicateConcurrentlyN :: forall (m :: * -> *) a.
(HasCallStack, MonadAsync m) =>
Positive Int -> Int -> m a -> m [a]
pooledReplicateConcurrentlyN Positive Int
numProcs Int
cnt m a
task =
if Int
cnt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1
then [a] -> m [a]
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
else Positive Int -> (Int -> m a) -> [Int] -> m [a]
forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, HasCallStack, Traversable t) =>
Positive Int -> (a -> m b) -> t a -> m (t b)
forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
Positive Int -> (a -> m b) -> t a -> m (t b)
pooledMapConcurrentlyN Positive Int
numProcs (m a -> Int -> m a
forall a b. a -> b -> a
const m a
task) [Int
1 .. Int
cnt]
{-# INLINEABLE pooledReplicateConcurrentlyN #-}
pooledReplicateConcurrently ::
forall m a.
( HasCallStack,
MonadAsync m
) =>
Positive Int ->
m a ->
m [a]
pooledReplicateConcurrently :: forall (m :: * -> *) a.
(HasCallStack, MonadAsync m) =>
Positive Int -> m a -> m [a]
pooledReplicateConcurrently (MkPositive Int
cnt) m a
task =
if Int
cnt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1
then [a] -> m [a]
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
else (Int -> m a) -> [Int] -> m [a]
forall (m :: * -> *) (t :: * -> *) a b.
(MonadAsync m, HasCallStack, Traversable t) =>
(a -> m b) -> t a -> m (t b)
forall (t :: * -> *) a b.
(HasCallStack, Traversable t) =>
(a -> m b) -> t a -> m (t b)
pooledMapConcurrently (m a -> Int -> m a
forall a b. a -> b -> a
const m a
task) [Int
1 .. Int
cnt]
{-# INLINEABLE pooledReplicateConcurrently #-}
pooledReplicateConcurrentlyN_ ::
forall m a.
( HasCallStack,
MonadAsync m
) =>
Positive Int ->
Int ->
m a ->
m ()
pooledReplicateConcurrentlyN_ :: forall (m :: * -> *) a.
(HasCallStack, MonadAsync m) =>
Positive Int -> Int -> m a -> m ()
pooledReplicateConcurrentlyN_ Positive Int
numProcs Int
cnt m a
task =
if Int
cnt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1
then () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
else Positive Int -> (Int -> m a) -> [Int] -> m ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f, HasCallStack) =>
Positive Int -> (a -> m b) -> f a -> m ()
forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
Positive Int -> (a -> m b) -> f a -> m ()
pooledMapConcurrentlyN_ Positive Int
numProcs (m a -> Int -> m a
forall a b. a -> b -> a
const m a
task) [Int
1 .. Int
cnt]
{-# INLINEABLE pooledReplicateConcurrentlyN_ #-}
pooledReplicateConcurrently_ ::
forall m a.
( HasCallStack,
MonadAsync m
) =>
Int ->
m a ->
m ()
pooledReplicateConcurrently_ :: forall (m :: * -> *) a.
(HasCallStack, MonadAsync m) =>
Int -> m a -> m ()
pooledReplicateConcurrently_ Int
cnt m a
task =
if Int
cnt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1
then () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
else (Int -> m a) -> [Int] -> m ()
forall (m :: * -> *) (f :: * -> *) a b.
(MonadAsync m, Foldable f, HasCallStack) =>
(a -> m b) -> f a -> m ()
forall (f :: * -> *) a b.
(Foldable f, HasCallStack) =>
(a -> m b) -> f a -> m ()
pooledMapConcurrently_ (m a -> Int -> m a
forall a b. a -> b -> a
const m a
task) [Int
1 .. Int
cnt]
{-# INLINEABLE pooledReplicateConcurrently_ #-}