| Copyright | Copyright (C) 2012-2018 Mitsutoshi Aoe | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Mitsutoshi Aoe <maoe@foldr.in> | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Control.Concurrent.Async.Lifted
Contents
Description
This is a wrapped version of Control.Concurrent.Async with types generalized
from IO to all monads in either MonadBase or MonadBaseControl.
All the functions restore the monadic effects in the forked computation unless specified otherwise.
If your monad stack satisfies StM m a ~ aControl.Concurrent.Async.Lifted.Safe module, which prevents you from
messing up monadic effects.
Synopsis
- data Async a
- async :: MonadBaseControl IO m => m a -> m (Async (StM m a))
- asyncBound :: MonadBaseControl IO m => m a -> m (Async (StM m a))
- asyncOn :: MonadBaseControl IO m => Int -> m a -> m (Async (StM m a))
- asyncWithUnmask :: MonadBaseControl IO m => ((forall b. m b -> m b) -> m a) -> m (Async (StM m a))
- asyncOnWithUnmask :: MonadBaseControl IO m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async (StM m a))
- withAsync :: MonadBaseControl IO m => m a -> (Async (StM m a) -> m b) -> m b
- withAsyncBound :: MonadBaseControl IO m => m a -> (Async (StM m a) -> m b) -> m b
- withAsyncOn :: MonadBaseControl IO m => Int -> m a -> (Async (StM m a) -> m b) -> m b
- withAsyncWithUnmask :: MonadBaseControl IO m => ((forall c. m c -> m c) -> m a) -> (Async (StM m a) -> m b) -> m b
- withAsyncOnWithUnmask :: MonadBaseControl IO m => Int -> ((forall c. m c -> m c) -> m a) -> (Async (StM m a) -> m b) -> m b
- wait :: MonadBaseControl IO m => Async (StM m a) -> m a
- poll :: MonadBaseControl IO m => Async (StM m a) -> m (Maybe (Either SomeException a))
- waitCatch :: MonadBaseControl IO m => Async (StM m a) -> m (Either SomeException a)
- cancel :: MonadBase IO m => Async a -> m ()
- uninterruptibleCancel :: MonadBase IO m => Async a -> m ()
- cancelWith :: (MonadBase IO m, Exception e) => Async a -> e -> m ()
- asyncThreadId :: Async a -> ThreadId
- data AsyncCancelled = AsyncCancelled
- waitSTM :: Async a -> STM a
- pollSTM :: Async a -> STM (Maybe (Either SomeException a))
- waitCatchSTM :: Async a -> STM (Either SomeException a)
- waitAny :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), a)
- waitAnyCatch :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), Either SomeException a)
- waitAnyCancel :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), a)
- waitAnyCatchCancel :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), Either SomeException a)
- waitEither :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either a b)
- waitEitherCatch :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either (Either SomeException a) (Either SomeException b))
- waitEitherCancel :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either a b)
- waitEitherCatchCancel :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either (Either SomeException a) (Either SomeException b))
- waitEither_ :: MonadBase IO m => Async a -> Async b -> m ()
- waitBoth :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (a, b)
- waitAnySTM :: [Async a] -> STM (Async a, a)
- waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a)
- waitEitherSTM :: Async a -> Async b -> STM (Either a b)
- waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b))
- waitEitherSTM_ :: Async a -> Async b -> STM ()
- waitBothSTM :: Async a -> Async b -> STM (a, b)
- link :: MonadBase IO m => Async a -> m ()
- link2 :: MonadBase IO m => Async a -> Async b -> m ()
- data ExceptionInLinkedThread where- ExceptionInLinkedThread :: forall a. Async a -> SomeException -> ExceptionInLinkedThread
 
- race :: MonadBaseControl IO m => m a -> m b -> m (Either a b)
- race_ :: MonadBaseControl IO m => m a -> m b -> m ()
- concurrently :: MonadBaseControl IO m => m a -> m b -> m (a, b)
- concurrently_ :: MonadBaseControl IO m => m a -> m b -> m ()
- mapConcurrently :: (Traversable t, MonadBaseControl IO m) => (a -> m b) -> t a -> m (t b)
- mapConcurrently_ :: (Foldable t, MonadBaseControl IO m) => (a -> m b) -> t a -> m ()
- forConcurrently :: (Traversable t, MonadBaseControl IO m) => t a -> (a -> m b) -> m (t b)
- forConcurrently_ :: (Foldable t, MonadBaseControl IO m) => t a -> (a -> m b) -> m ()
- replicateConcurrently :: MonadBaseControl IO m => Int -> m a -> m [a]
- replicateConcurrently_ :: MonadBaseControl IO m => Int -> m a -> m ()
- newtype Concurrently m a = Concurrently {- runConcurrently :: m a
 
- compareAsyncs :: Async a -> Async b -> Ordering
Asynchronous actions
An asynchronous action spawned by async or withAsync.
 Asynchronous actions are executed in a separate thread, and
 operations are provided for waiting for asynchronous actions to
 complete and obtaining their results (see e.g. wait).
Instances
| Functor Async | |
| Eq (Async a) | |
| Ord (Async a) | |
| Defined in Control.Concurrent.Async | |
| Hashable (Async a) | |
| Defined in Control.Concurrent.Async | |
Spawning
asyncBound :: MonadBaseControl IO m => m a -> m (Async (StM m a)) Source #
Generalized version of asyncBound.
asyncOn :: MonadBaseControl IO m => Int -> m a -> m (Async (StM m a)) Source #
Generalized version of asyncOn.
asyncWithUnmask :: MonadBaseControl IO m => ((forall b. m b -> m b) -> m a) -> m (Async (StM m a)) Source #
Generalized version of asyncWithUnmask.
asyncOnWithUnmask :: MonadBaseControl IO m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async (StM m a)) Source #
Generalized version of asyncOnWithUnmask.
Spawning with automatic cancelation
withAsync :: MonadBaseControl IO m => m a -> (Async (StM m a) -> m b) -> m b Source #
Generalized version of withAsync.
withAsyncBound :: MonadBaseControl IO m => m a -> (Async (StM m a) -> m b) -> m b Source #
Generalized version of withAsyncBound.
withAsyncOn :: MonadBaseControl IO m => Int -> m a -> (Async (StM m a) -> m b) -> m b Source #
Generalized version of withAsyncOn.
withAsyncWithUnmask :: MonadBaseControl IO m => ((forall c. m c -> m c) -> m a) -> (Async (StM m a) -> m b) -> m b Source #
Generalized version of withAsyncWithUnmask.
withAsyncOnWithUnmask :: MonadBaseControl IO m => Int -> ((forall c. m c -> m c) -> m a) -> (Async (StM m a) -> m b) -> m b Source #
Generalized version of withAsyncOnWithUnmask.
Quering Asyncs
poll :: MonadBaseControl IO m => Async (StM m a) -> m (Maybe (Either SomeException a)) Source #
Generalized version of poll.
waitCatch :: MonadBaseControl IO m => Async (StM m a) -> m (Either SomeException a) Source #
Generalized version of waitCatch.
uninterruptibleCancel :: MonadBase IO m => Async a -> m () Source #
Generalized version of uninterruptibleCancel.
cancelWith :: (MonadBase IO m, Exception e) => Async a -> e -> m () Source #
Generalized version of cancelWith.
data AsyncCancelled #
The exception thrown by cancel to terminate a thread.
Constructors
| AsyncCancelled | 
Instances
| Eq AsyncCancelled | |
| Defined in Control.Concurrent.Async Methods (==) :: AsyncCancelled -> AsyncCancelled -> Bool # (/=) :: AsyncCancelled -> AsyncCancelled -> Bool # | |
| Show AsyncCancelled | |
| Defined in Control.Concurrent.Async Methods showsPrec :: Int -> AsyncCancelled -> ShowS # show :: AsyncCancelled -> String # showList :: [AsyncCancelled] -> ShowS # | |
| Exception AsyncCancelled | |
| Defined in Control.Concurrent.Async Methods toException :: AsyncCancelled -> SomeException # | |
STM operations
pollSTM :: Async a -> STM (Maybe (Either SomeException a)) #
A version of poll that can be used inside an STM transaction.
waitCatchSTM :: Async a -> STM (Either SomeException a) #
A version of waitCatch that can be used inside an STM transaction.
Waiting for multiple Asyncs
waitAny :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), a) Source #
Generalized version of waitAny.
waitAnyCatch :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), Either SomeException a) Source #
Generalized version of waitAnyCatch.
waitAnyCancel :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), a) Source #
Generalized version of waitAnyCancel.
waitAnyCatchCancel :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), Either SomeException a) Source #
Generalized version of waitAnyCatchCancel.
waitEither :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either a b) Source #
Generalized version of waitEither.
waitEitherCatch :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either (Either SomeException a) (Either SomeException b)) Source #
Generalized version of waitEitherCatch.
waitEitherCancel :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either a b) Source #
Generalized version of waitEitherCancel.
waitEitherCatchCancel :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either (Either SomeException a) (Either SomeException b)) Source #
Generalized version of waitEitherCatchCancel.
waitEither_ :: MonadBase IO m => Async a -> Async b -> m () Source #
Generalized version of waitEither_.
NOTE: This function discards the monadic effects besides IO in the forked computation.
waitBoth :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (a, b) Source #
Generalized version of waitBoth.
Waiting for multiple Asyncs in STM
waitAnySTM :: [Async a] -> STM (Async a, a) #
A version of waitAny that can be used inside an STM transaction.
Since: async-2.1.0
waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a) #
A version of waitAnyCatch that can be used inside an STM transaction.
Since: async-2.1.0
waitEitherSTM :: Async a -> Async b -> STM (Either a b) #
A version of waitEither that can be used inside an STM transaction.
Since: async-2.1.0
waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b)) #
A version of waitEitherCatch that can be used inside an STM transaction.
Since: async-2.1.0
waitEitherSTM_ :: Async a -> Async b -> STM () #
A version of waitEither_ that can be used inside an STM transaction.
Since: async-2.1.0
waitBothSTM :: Async a -> Async b -> STM (a, b) #
A version of waitBoth that can be used inside an STM transaction.
Since: async-2.1.0
Linking
data ExceptionInLinkedThread where #
Constructors
| ExceptionInLinkedThread :: forall a. Async a -> SomeException -> ExceptionInLinkedThread | 
Instances
| Show ExceptionInLinkedThread | |
| Defined in Control.Concurrent.Async Methods showsPrec :: Int -> ExceptionInLinkedThread -> ShowS # show :: ExceptionInLinkedThread -> String # showList :: [ExceptionInLinkedThread] -> ShowS # | |
| Exception ExceptionInLinkedThread | |
| Defined in Control.Concurrent.Async | |
Convenient utilities
race_ :: MonadBaseControl IO m => m a -> m b -> m () Source #
Generalized version of race_.
NOTE: This function discards the monadic effects besides IO in the forked computation.
concurrently :: MonadBaseControl IO m => m a -> m b -> m (a, b) Source #
Generalized version of concurrently.
concurrently_ :: MonadBaseControl IO m => m a -> m b -> m () Source #
Generalized version of concurrently_.
mapConcurrently :: (Traversable t, MonadBaseControl IO m) => (a -> m b) -> t a -> m (t b) Source #
Generalized version of mapConcurrently.
mapConcurrently_ :: (Foldable t, MonadBaseControl IO m) => (a -> m b) -> t a -> m () Source #
Generalized version of mapConcurrently_.
forConcurrently :: (Traversable t, MonadBaseControl IO m) => t a -> (a -> m b) -> m (t b) Source #
Generalized version of forConcurrently.
forConcurrently_ :: (Foldable t, MonadBaseControl IO m) => t a -> (a -> m b) -> m () Source #
Generalized version of forConcurrently_.
replicateConcurrently :: MonadBaseControl IO m => Int -> m a -> m [a] Source #
Generalized version of replicateConcurrently.
replicateConcurrently_ :: MonadBaseControl IO m => Int -> m a -> m () Source #
Generalized version of replicateConcurrently_.
newtype Concurrently m a Source #
Generalized version of Concurrently.
A value of type Concurrently m aConcurrently values, using the Applicative and
 Alternative instances.
Calling runConcurrently on a value of type Concurrently m aa.
For example
(page1, page2, page3) <-runConcurrently$ (,,)<$>Concurrently(getURL "url1")<*>Concurrently(getURL "url2")<*>Concurrently(getURL "url3")
Constructors
| Concurrently | |
| Fields 
 | |