{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Control.Concurrent.Async.Lifted.Safe
(
A.Async
, Pure
, Forall
, async, asyncBound, asyncOn, asyncWithUnmask, asyncOnWithUnmask
, withAsync, withAsyncBound, withAsyncOn
, withAsyncWithUnmask, withAsyncOnWithUnmask
, wait, poll, waitCatch
, cancel
, uninterruptibleCancel
, cancelWith
, A.asyncThreadId
, A.AsyncCancelled(..)
, A.waitSTM, A.pollSTM, A.waitCatchSTM
, waitAny, waitAnyCatch, waitAnyCancel, waitAnyCatchCancel
, waitEither, waitEitherCatch, waitEitherCancel, waitEitherCatchCancel
, waitEither_
, waitBoth
, A.waitAnySTM
, A.waitAnyCatchSTM
, A.waitEitherSTM
, A.waitEitherCatchSTM
, A.waitEitherSTM_
, A.waitBothSTM
, Unsafe.link, Unsafe.link2
, A.ExceptionInLinkedThread(..)
, race, race_, concurrently, concurrently_
, mapConcurrently, mapConcurrently_
, forConcurrently, forConcurrently_
, replicateConcurrently, replicateConcurrently_
, Concurrently(..)
, A.compareAsyncs
)
where
import Control.Applicative
import Control.Concurrent (threadDelay)
import Control.Monad
import Data.Foldable (fold)
import Control.Concurrent.Async (Async)
import Control.Exception.Lifted (SomeException, Exception)
import Control.Monad.Base (MonadBase(..))
import Control.Monad.Trans.Control hiding (restoreM)
import Data.Constraint ((\\), (:-))
import Data.Constraint.Forall (Forall, inst)
import qualified Control.Concurrent.Async as A
import qualified Control.Concurrent.Async.Lifted as Unsafe
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 710
import Data.Foldable
import Data.Traversable
#endif
#if !MIN_VERSION_base(4, 8, 0)
import Data.Monoid (Monoid(mappend, mempty))
#elif MIN_VERSION_base(4, 9, 0) && !MIN_VERSION_base(4, 13, 0)
import Data.Semigroup (Semigroup((<>)))
#endif
async
:: forall m a. (MonadBaseControl IO m, Forall (Pure m))
=> m a -> m (Async a)
async :: m a -> m (Async a)
async = Pure m a => m a -> m (Async a)
forall (m :: * -> *) a.
MonadBaseControl IO m =>
m a -> m (Async (StM m a))
Unsafe.async
(Pure m a => m a -> m (Async a))
-> (Forall_ (Pure m) :- Pure m a) -> m a -> m (Async a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
asyncBound
:: forall m a. (MonadBaseControl IO m, Forall (Pure m))
=> m a -> m (Async a)
asyncBound :: m a -> m (Async a)
asyncBound = Pure m a => m a -> m (Async a)
forall (m :: * -> *) a.
MonadBaseControl IO m =>
m a -> m (Async (StM m a))
Unsafe.asyncBound
(Pure m a => m a -> m (Async a))
-> (Forall_ (Pure m) :- Pure m a) -> m a -> m (Async a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
asyncOn
:: forall m a. (MonadBaseControl IO m, Forall (Pure m))
=> Int -> m a -> m (Async a)
asyncOn :: Int -> m a -> m (Async a)
asyncOn Int
cpu m a
m = Int -> m a -> m (Async (StM m a))
forall (m :: * -> *) a.
MonadBaseControl IO m =>
Int -> m a -> m (Async (StM m a))
Unsafe.asyncOn Int
cpu m a
m
(Pure m a => m (Async a))
-> (Forall_ (Pure m) :- Pure m a) -> m (Async a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
asyncWithUnmask
:: forall m a. (MonadBaseControl IO m, Forall (Pure m))
=> ((forall b. m b -> m b) -> m a)
-> m (Async a)
asyncWithUnmask :: ((forall b. m b -> m b) -> m a) -> m (Async a)
asyncWithUnmask (forall b. m b -> m b) -> m a
restore = ((forall b. m b -> m b) -> m a) -> m (Async (StM m a))
forall (m :: * -> *) a.
MonadBaseControl IO m =>
((forall b. m b -> m b) -> m a) -> m (Async (StM m a))
Unsafe.asyncWithUnmask (forall b. m b -> m b) -> m a
restore
(Pure m a => m (Async a))
-> (Forall_ (Pure m) :- Pure m a) -> m (Async a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
asyncOnWithUnmask
:: forall m a. (MonadBaseControl IO m, Forall (Pure m))
=> Int
-> ((forall b. m b -> m b) -> m a)
-> m (Async a)
asyncOnWithUnmask :: Int -> ((forall b. m b -> m b) -> m a) -> m (Async a)
asyncOnWithUnmask Int
cpu (forall b. m b -> m b) -> m a
restore = Int -> ((forall b. m b -> m b) -> m a) -> m (Async (StM m a))
forall (m :: * -> *) a.
MonadBaseControl IO m =>
Int -> ((forall b. m b -> m b) -> m a) -> m (Async (StM m a))
Unsafe.asyncOnWithUnmask Int
cpu (forall b. m b -> m b) -> m a
restore
(Pure m a => m (Async a))
-> (Forall_ (Pure m) :- Pure m a) -> m (Async a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
withAsync
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> m a
-> (Async a -> m b)
-> m b
withAsync :: m a -> (Async a -> m b) -> m b
withAsync = Pure m a => m a -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
MonadBaseControl IO m =>
m a -> (Async (StM m a) -> m b) -> m b
Unsafe.withAsync
(Pure m a => m a -> (Async a -> m b) -> m b)
-> (Forall_ (Pure m) :- Pure m a) -> m a -> (Async a -> m b) -> m b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
withAsyncBound
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> m a
-> (Async a -> m b)
-> m b
withAsyncBound :: m a -> (Async a -> m b) -> m b
withAsyncBound = Pure m a => m a -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
MonadBaseControl IO m =>
m a -> (Async (StM m a) -> m b) -> m b
Unsafe.withAsyncBound
(Pure m a => m a -> (Async a -> m b) -> m b)
-> (Forall_ (Pure m) :- Pure m a) -> m a -> (Async a -> m b) -> m b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
withAsyncOn
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> Int
-> m a
-> (Async a -> m b)
-> m b
withAsyncOn :: Int -> m a -> (Async a -> m b) -> m b
withAsyncOn = Pure m a => Int -> m a -> (Async a -> m b) -> m b
forall (m :: * -> *) a b.
MonadBaseControl IO m =>
Int -> m a -> (Async (StM m a) -> m b) -> m b
Unsafe.withAsyncOn
(Pure m a => Int -> m a -> (Async a -> m b) -> m b)
-> (Forall_ (Pure m) :- Pure m a)
-> Int
-> m a
-> (Async a -> m b)
-> m b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
withAsyncWithUnmask
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> ((forall c. m c -> m c) -> m a)
-> (Async a -> m b)
-> m b
withAsyncWithUnmask :: ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
withAsyncWithUnmask (forall c. m c -> m c) -> m a
restore = ((forall c. m c -> m c) -> m a) -> (Async (StM m a) -> m b) -> m b
forall (m :: * -> *) a b.
MonadBaseControl IO m =>
((forall c. m c -> m c) -> m a) -> (Async (StM m a) -> m b) -> m b
Unsafe.withAsyncWithUnmask (forall c. m c -> m c) -> m a
restore
(Pure m a => (Async a -> m b) -> m b)
-> (Forall_ (Pure m) :- Pure m a) -> (Async a -> m b) -> m b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
withAsyncOnWithUnmask
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> Int
-> ((forall c. m c -> m c) -> m a)
-> (Async a -> m b)
-> m b
withAsyncOnWithUnmask :: Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
withAsyncOnWithUnmask Int
cpu (forall c. m c -> m c) -> m a
restore = Int
-> ((forall c. m c -> m c) -> m a)
-> (Async (StM m a) -> m b)
-> m b
forall (m :: * -> *) a b.
MonadBaseControl IO m =>
Int
-> ((forall c. m c -> m c) -> m a)
-> (Async (StM m a) -> m b)
-> m b
Unsafe.withAsyncOnWithUnmask Int
cpu (forall c. m c -> m c) -> m a
restore
(Pure m a => (Async a -> m b) -> m b)
-> (Forall_ (Pure m) :- Pure m a) -> (Async a -> m b) -> m b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
wait
:: forall m a. (MonadBase IO m, Forall (Pure m))
=> Async a -> m a
wait :: Async a -> m a
wait = IO a -> m a
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO a -> m a) -> (Async a -> IO a) -> Async a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> IO a
forall a. Async a -> IO a
A.wait
(Pure m a => Async a -> m a)
-> (Forall_ (Pure m) :- Pure m a) -> Async a -> m a
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
poll
:: forall m a. (MonadBase IO m, Forall (Pure m))
=> Async a
-> m (Maybe (Either SomeException a))
poll :: Async a -> m (Maybe (Either SomeException a))
poll = IO (Maybe (Either SomeException a))
-> m (Maybe (Either SomeException a))
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Maybe (Either SomeException a))
-> m (Maybe (Either SomeException a)))
-> (Async a -> IO (Maybe (Either SomeException a)))
-> Async a
-> m (Maybe (Either SomeException a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> IO (Maybe (Either SomeException a))
forall a. Async a -> IO (Maybe (Either SomeException a))
A.poll
(Pure m a => Async a -> m (Maybe (Either SomeException a)))
-> (Forall_ (Pure m) :- Pure m a)
-> Async a
-> m (Maybe (Either SomeException a))
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
waitCatch
:: forall m a. (MonadBase IO m, Forall (Pure m))
=> Async a
-> m (Either SomeException a)
waitCatch :: Async a -> m (Either SomeException a)
waitCatch = IO (Either SomeException a) -> m (Either SomeException a)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Either SomeException a) -> m (Either SomeException a))
-> (Async a -> IO (Either SomeException a))
-> Async a
-> m (Either SomeException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> IO (Either SomeException a)
forall a. Async a -> IO (Either SomeException a)
A.waitCatch
(Pure m a => Async a -> m (Either SomeException a))
-> (Forall_ (Pure m) :- Pure m a)
-> Async a
-> m (Either SomeException a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
cancel :: MonadBase IO m => Async a -> m ()
cancel :: Async a -> m ()
cancel = Async a -> m ()
forall (m :: * -> *) a. MonadBase IO m => Async a -> m ()
Unsafe.cancel
cancelWith :: (MonadBase IO m, Exception e) => Async a -> e -> m ()
cancelWith :: Async a -> e -> m ()
cancelWith = Async a -> e -> m ()
forall (m :: * -> *) e a.
(MonadBase IO m, Exception e) =>
Async a -> e -> m ()
Unsafe.cancelWith
uninterruptibleCancel :: MonadBase IO m => Async a -> m ()
uninterruptibleCancel :: Async a -> m ()
uninterruptibleCancel = Async a -> m ()
forall (m :: * -> *) a. MonadBase IO m => Async a -> m ()
Unsafe.uninterruptibleCancel
waitAny
:: forall m a. (MonadBase IO m, Forall (Pure m))
=> [Async a] -> m (Async a, a)
waitAny :: [Async a] -> m (Async a, a)
waitAny = IO (Async a, a) -> m (Async a, a)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Async a, a) -> m (Async a, a))
-> ([Async a] -> IO (Async a, a)) -> [Async a] -> m (Async a, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> IO (Async a, a)
forall a. [Async a] -> IO (Async a, a)
A.waitAny
(Pure m a => [Async a] -> m (Async a, a))
-> (Forall_ (Pure m) :- Pure m a) -> [Async a] -> m (Async a, a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
waitAnyCatch
:: forall m a. (MonadBase IO m, Forall (Pure m))
=> [Async a]
-> m (Async a, Either SomeException a)
waitAnyCatch :: [Async a] -> m (Async a, Either SomeException a)
waitAnyCatch = IO (Async a, Either SomeException a)
-> m (Async a, Either SomeException a)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Async a, Either SomeException a)
-> m (Async a, Either SomeException a))
-> ([Async a] -> IO (Async a, Either SomeException a))
-> [Async a]
-> m (Async a, Either SomeException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> IO (Async a, Either SomeException a)
forall a. [Async a] -> IO (Async a, Either SomeException a)
A.waitAnyCatch
(Pure m a => [Async a] -> m (Async a, Either SomeException a))
-> (Forall_ (Pure m) :- Pure m a)
-> [Async a]
-> m (Async a, Either SomeException a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
waitAnyCancel
:: forall m a. (MonadBase IO m, Forall (Pure m))
=> [Async a]
-> m (Async a, a)
waitAnyCancel :: [Async a] -> m (Async a, a)
waitAnyCancel = IO (Async a, a) -> m (Async a, a)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Async a, a) -> m (Async a, a))
-> ([Async a] -> IO (Async a, a)) -> [Async a] -> m (Async a, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> IO (Async a, a)
forall a. [Async a] -> IO (Async a, a)
A.waitAnyCancel
(Pure m a => [Async a] -> m (Async a, a))
-> (Forall_ (Pure m) :- Pure m a) -> [Async a] -> m (Async a, a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
waitAnyCatchCancel
:: forall m a. (MonadBase IO m, Forall (Pure m))
=> [Async a]
-> m (Async a, Either SomeException a)
waitAnyCatchCancel :: [Async a] -> m (Async a, Either SomeException a)
waitAnyCatchCancel = IO (Async a, Either SomeException a)
-> m (Async a, Either SomeException a)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Async a, Either SomeException a)
-> m (Async a, Either SomeException a))
-> ([Async a] -> IO (Async a, Either SomeException a))
-> [Async a]
-> m (Async a, Either SomeException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Async a] -> IO (Async a, Either SomeException a)
forall a. [Async a] -> IO (Async a, Either SomeException a)
A.waitAnyCatchCancel
(Pure m a => [Async a] -> m (Async a, Either SomeException a))
-> (Forall_ (Pure m) :- Pure m a)
-> [Async a]
-> m (Async a, Either SomeException a)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
waitEither
:: forall m a b. (MonadBase IO m, Forall (Pure m))
=> Async a
-> Async b
-> m (Either a b)
waitEither :: Async a -> Async b -> m (Either a b)
waitEither = (IO (Either a b) -> m (Either a b)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Either a b) -> m (Either a b))
-> (Async b -> IO (Either a b)) -> Async b -> m (Either a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Async b -> IO (Either a b)) -> Async b -> m (Either a b))
-> (Async a -> Async b -> IO (Either a b))
-> Async a
-> Async b
-> m (Either a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> IO (Either a b)
forall a b. Async a -> Async b -> IO (Either a b)
A.waitEither
(Pure m a => Async a -> Async b -> m (Either a b))
-> (Forall_ (Pure m) :- Pure m a)
-> Async a
-> Async b
-> m (Either a b)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
(Pure m b => Async a -> Async b -> m (Either a b))
-> (Forall_ (Pure m) :- Pure m b)
-> Async a
-> Async b
-> m (Either a b)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m b
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m b)
waitEitherCatch
:: forall m a b. (MonadBase IO m, Forall (Pure m))
=> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatch :: Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatch = (IO (Either (Either SomeException a) (Either SomeException b))
-> m (Either (Either SomeException a) (Either SomeException b))
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Either (Either SomeException a) (Either SomeException b))
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Async b
-> IO (Either (Either SomeException a) (Either SomeException b)))
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Async b
-> IO (Either (Either SomeException a) (Either SomeException b)))
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b)))
-> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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))
A.waitEitherCatch
(Pure m a =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Forall_ (Pure m) :- Pure m a)
-> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
(Pure m b =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Forall_ (Pure m) :- Pure m b)
-> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m b
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m b)
waitEitherCancel
:: forall m a b. (MonadBase IO m, Forall (Pure m))
=> Async a
-> Async b
-> m (Either a b)
waitEitherCancel :: Async a -> Async b -> m (Either a b)
waitEitherCancel = (IO (Either a b) -> m (Either a b)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Either a b) -> m (Either a b))
-> (Async b -> IO (Either a b)) -> Async b -> m (Either a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Async b -> IO (Either a b)) -> Async b -> m (Either a b))
-> (Async a -> Async b -> IO (Either a b))
-> Async a
-> Async b
-> m (Either a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> IO (Either a b)
forall a b. Async a -> Async b -> IO (Either a b)
A.waitEitherCancel
(Pure m a => Async a -> Async b -> m (Either a b))
-> (Forall_ (Pure m) :- Pure m a)
-> Async a
-> Async b
-> m (Either a b)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
(Pure m b => Async a -> Async b -> m (Either a b))
-> (Forall_ (Pure m) :- Pure m b)
-> Async a
-> Async b
-> m (Either a b)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m b
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m b)
waitEitherCatchCancel
:: forall m a b. (MonadBase IO m, Forall (Pure m))
=> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatchCancel :: Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
waitEitherCatchCancel = (IO (Either (Either SomeException a) (Either SomeException b))
-> m (Either (Either SomeException a) (Either SomeException b))
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (Either (Either SomeException a) (Either SomeException b))
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Async b
-> IO (Either (Either SomeException a) (Either SomeException b)))
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Async b
-> IO (Either (Either SomeException a) (Either SomeException b)))
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Async a
-> Async b
-> IO (Either (Either SomeException a) (Either SomeException b)))
-> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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))
A.waitEitherCatchCancel
(Pure m a =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Forall_ (Pure m) :- Pure m a)
-> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
(Pure m b =>
Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b)))
-> (Forall_ (Pure m) :- Pure m b)
-> Async a
-> Async b
-> m (Either (Either SomeException a) (Either SomeException b))
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m b
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m b)
waitEither_ :: MonadBase IO m => Async a -> Async b -> m ()
waitEither_ :: Async a -> Async b -> m ()
waitEither_ = Async a -> Async b -> m ()
forall (m :: * -> *) a b.
MonadBase IO m =>
Async a -> Async b -> m ()
Unsafe.waitEither_
waitBoth
:: forall m a b. (MonadBase IO m, Forall (Pure m))
=> Async a
-> Async b
-> m (a, b)
waitBoth :: Async a -> Async b -> m (a, b)
waitBoth = (IO (a, b) -> m (a, b)
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (IO (a, b) -> m (a, b))
-> (Async b -> IO (a, b)) -> Async b -> m (a, b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Async b -> IO (a, b)) -> Async b -> m (a, b))
-> (Async a -> Async b -> IO (a, b))
-> Async a
-> Async b
-> m (a, b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Async a -> Async b -> IO (a, b)
forall a b. Async a -> Async b -> IO (a, b)
A.waitBoth
(Pure m a => Async a -> Async b -> m (a, b))
-> (Forall_ (Pure m) :- Pure m a) -> Async a -> Async b -> m (a, b)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
(Pure m b => Async a -> Async b -> m (a, b))
-> (Forall_ (Pure m) :- Pure m b) -> Async a -> Async b -> m (a, b)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m b
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m b)
race
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> m a -> m b -> m (Either a b)
race :: m a -> m b -> m (Either a b)
race = (IO a -> IO b -> IO (Either a b)) -> m a -> m b -> m (Either a b)
forall (base :: * -> *) (m :: * -> *) a b c.
(MonadBaseControl base m, Forall (Pure m)) =>
(base a -> base b -> base c) -> m a -> m b -> m c
liftBaseOp2_ IO a -> IO b -> IO (Either a b)
forall a b. IO a -> IO b -> IO (Either a b)
A.race
race_
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> m a -> m b -> m ()
race_ :: m a -> m b -> m ()
race_ = (IO a -> IO b -> IO ()) -> m a -> m b -> m ()
forall (base :: * -> *) (m :: * -> *) a b c.
(MonadBaseControl base m, Forall (Pure m)) =>
(base a -> base b -> base c) -> m a -> m b -> m c
liftBaseOp2_ IO a -> IO b -> IO ()
forall a b. IO a -> IO b -> IO ()
A.race_
concurrently
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> m a -> m b -> m (a, b)
concurrently :: m a -> m b -> m (a, b)
concurrently = (IO a -> IO b -> IO (a, b)) -> m a -> m b -> m (a, b)
forall (base :: * -> *) (m :: * -> *) a b c.
(MonadBaseControl base m, Forall (Pure m)) =>
(base a -> base b -> base c) -> m a -> m b -> m c
liftBaseOp2_ IO a -> IO b -> IO (a, b)
forall a b. IO a -> IO b -> IO (a, b)
A.concurrently
concurrently_
:: forall m a b. (MonadBaseControl IO m, Forall (Pure m))
=> m a -> m b -> m ()
concurrently_ :: m a -> m b -> m ()
concurrently_ = (IO a -> IO b -> IO ()) -> m a -> m b -> m ()
forall (base :: * -> *) (m :: * -> *) a b c.
(MonadBaseControl base m, Forall (Pure m)) =>
(base a -> base b -> base c) -> m a -> m b -> m c
liftBaseOp2_ IO a -> IO b -> IO ()
forall a b. IO a -> IO b -> IO ()
A.concurrently_
liftBaseOp2_
:: forall base m a b c. (MonadBaseControl base m, Forall (Pure m))
=> (base a -> base b -> base c)
-> m a -> m b -> m c
liftBaseOp2_ :: (base a -> base b -> base c) -> m a -> m b -> m c
liftBaseOp2_ base a -> base b -> base c
f m a
left m b
right = (RunInBase m base -> base c) -> m c
forall (b :: * -> *) (m :: * -> *) a.
MonadBaseControl b m =>
(RunInBase m b -> b a) -> m a
liftBaseWith ((RunInBase m base -> base c) -> m c)
-> (RunInBase m base -> base c) -> m c
forall a b. (a -> b) -> a -> b
$ \RunInBase m base
run -> base a -> base b -> base c
f
(m a -> base (StM m a)
RunInBase m base
run m a
left (Pure m a => base a) -> (Forall_ (Pure m) :- Pure m a) -> base a
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a))
(m b -> base (StM m b)
RunInBase m base
run m b
right (Pure m b => base b) -> (Forall_ (Pure m) :- Pure m b) -> base b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m b
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m b))
mapConcurrently
:: (Traversable t, MonadBaseControl IO m, Forall (Pure m))
=> (a -> m b)
-> t a
-> m (t b)
mapConcurrently :: (a -> m b) -> t a -> m (t b)
mapConcurrently a -> m b
f = Concurrently m (t b) -> m (t b)
forall (m :: * -> *) a. 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)
traverse (m b -> Concurrently m b
forall (m :: * -> *) a. Forall (Pure m) => 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)
mapConcurrently_
:: (Foldable t, MonadBaseControl IO m, Forall (Pure m))
=> (a -> m b)
-> t a
-> m ()
mapConcurrently_ :: (a -> m b) -> t a -> m ()
mapConcurrently_ a -> m b
f = Concurrently m () -> m ()
forall (m :: * -> *) a. Concurrently m a -> m a
runConcurrently (Concurrently m () -> m ())
-> (t a -> Concurrently m ()) -> t a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Concurrently m ()) -> t a -> Concurrently m ()
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (m () -> Concurrently m ()
forall (m :: * -> *) a. Forall (Pure m) => 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)
forConcurrently
:: (Traversable t, MonadBaseControl IO m, Forall (Pure m))
=> t a
-> (a -> m b)
-> m (t b)
forConcurrently :: 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 (t :: * -> *) (m :: * -> *) a b.
(Traversable t, MonadBaseControl IO m, Forall (Pure m)) =>
(a -> m b) -> t a -> m (t b)
mapConcurrently
forConcurrently_
:: (Foldable t, MonadBaseControl IO m, Forall (Pure m))
=> t a
-> (a -> m b)
-> m ()
forConcurrently_ :: t a -> (a -> m b) -> m ()
forConcurrently_ = ((a -> m b) -> t a -> m ()) -> t a -> (a -> m b) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> m b) -> t a -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, MonadBaseControl IO m, Forall (Pure m)) =>
(a -> m b) -> t a -> m ()
mapConcurrently_
replicateConcurrently
:: (MonadBaseControl IO m, Forall (Pure m))
=> Int
-> m a
-> m [a]
replicateConcurrently :: Int -> m a -> m [a]
replicateConcurrently Int
n =
Concurrently m [a] -> m [a]
forall (m :: * -> *) a. 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
. [Concurrently m a] -> Concurrently m [a]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([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
. Int -> Concurrently m a -> [Concurrently m a]
forall a. Int -> a -> [a]
replicate Int
n (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 (m :: * -> *) a. Forall (Pure m) => m a -> Concurrently m a
Concurrently
replicateConcurrently_
:: (MonadBaseControl IO m, Forall (Pure m))
=> Int
-> m a
-> m ()
replicateConcurrently_ :: Int -> m a -> m ()
replicateConcurrently_ Int
n =
Concurrently m () -> m ()
forall (m :: * -> *) a. 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 (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
n (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 (m :: * -> *) a. Forall (Pure m) => 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
data Concurrently m a where
Concurrently
:: Forall (Pure m) => { Concurrently m a -> m a
runConcurrently :: m a } -> Concurrently m a
class StM m a ~ a => Pure m a
instance StM m a ~ a => Pure m a
instance Functor m => Functor (Concurrently m) where
fmap :: (a -> b) -> Concurrently m a -> Concurrently m b
fmap a -> b
f (Concurrently m a
a) = m b -> Concurrently m b
forall (m :: * -> *) a. Forall (Pure m) => 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 (MonadBaseControl IO m, Forall (Pure m)) =>
Applicative (Concurrently m) where
pure :: a -> Concurrently m a
pure = m a -> Concurrently m a
forall (m :: * -> *) a. Forall (Pure m) => 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 (f :: * -> *) a. Applicative f => a -> f a
pure
Concurrently (m (a -> b)
fs :: m (a -> b)) <*> :: Concurrently m (a -> b) -> Concurrently m a -> Concurrently m b
<*> Concurrently m a
as =
m b -> Concurrently m b
forall (m :: * -> *) a. Forall (Pure m) => m a -> Concurrently m a
Concurrently (((a -> b) -> a -> b) -> (a -> b, a) -> b
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (a -> b) -> a -> b
forall a b. (a -> b) -> a -> b
($) ((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 (m :: * -> *) a b.
(MonadBaseControl IO m, Forall (Pure m)) =>
m a -> m b -> m (a, b)
concurrently m (a -> b)
fs m a
as)
(Pure m a => Concurrently m b)
-> (Forall_ (Pure m) :- Pure m a) -> Concurrently m b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
(Pure m (a -> b) => Concurrently m b)
-> (Forall_ (Pure m) :- Pure m (a -> b)) -> Concurrently m b
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m (a -> b)
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m (a -> b))
instance (MonadBaseControl IO m, Forall (Pure m)) =>
Alternative (Concurrently m) where
empty :: Concurrently m a
empty = m a -> Concurrently m a
forall (m :: * -> *) a. Forall (Pure m) => m a -> Concurrently m a
Concurrently (m a -> Concurrently m a) -> m a -> Concurrently m a
forall a b. (a -> b) -> a -> b
$ (RunInBase m IO -> IO a) -> m a
forall (b :: * -> *) (m :: * -> *) a.
MonadBaseControl b m =>
(RunInBase m b -> b a) -> m a
liftBaseWith ((RunInBase m IO -> IO a) -> m a)
-> (RunInBase m IO -> IO a) -> m a
forall a b. (a -> b) -> a -> b
$ \RunInBase m IO
_ -> IO () -> IO a
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO a) -> IO () -> IO a
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay Int
forall a. Bounded a => a
maxBound
Concurrently (m a
as :: m a) <|> :: Concurrently m a -> Concurrently m a -> Concurrently m a
<|> Concurrently m a
bs =
m a -> Concurrently m a
forall (m :: * -> *) a. Forall (Pure m) => m a -> Concurrently m a
Concurrently ((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 (m :: * -> *) a b.
(MonadBaseControl IO m, Forall (Pure m)) =>
m a -> m b -> m (Either a b)
race m a
as m a
bs)
(Pure m a => Concurrently m a)
-> (Forall_ (Pure m) :- Pure m a) -> Concurrently m a
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (Forall (Pure m) :- Pure m a
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m a)
(Pure m Any => Concurrently m a)
-> (Forall_ (Pure m) :- Pure m Any) -> Concurrently m a
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ (forall b. Forall (Pure m) :- Pure m b
forall k (p :: k -> Constraint) (a :: k). Forall p :- p a
inst :: Forall (Pure m) :- Pure m b)
#if MIN_VERSION_base(4, 9, 0)
instance (MonadBaseControl IO m, Semigroup a, Forall (Pure m)) =>
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 (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 (MonadBaseControl IO m, Semigroup a, Monoid a, Forall (Pure m)) =>
Monoid (Concurrently m a) where
mempty :: Concurrently m a
mempty = 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
(<>)
#else
instance (MonadBaseControl IO m, Monoid a, Forall (Pure m)) =>
Monoid (Concurrently m a) where
mempty = pure mempty
mappend = liftA2 mappend
#endif