| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
UnliftIO.Async
Description
Unlifted Control.Concurrent.Async.
Since: 0.1.0.0
Synopsis
- data Async a
- async :: MonadUnliftIO m => m a -> m (Async a)
- asyncBound :: MonadUnliftIO m => m a -> m (Async a)
- asyncOn :: MonadUnliftIO m => Int -> m a -> m (Async a)
- asyncWithUnmask :: MonadUnliftIO m => ((forall b. m b -> m b) -> m a) -> m (Async a)
- asyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async a)
- withAsync :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b
- withAsyncBound :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b
- withAsyncOn :: MonadUnliftIO m => Int -> m a -> (Async a -> m b) -> m b
- withAsyncWithUnmask :: MonadUnliftIO m => ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
- withAsyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b
- wait :: MonadIO m => Async a -> m a
- poll :: MonadIO m => Async a -> m (Maybe (Either SomeException a))
- waitCatch :: MonadIO m => Async a -> m (Either SomeException a)
- cancel :: MonadIO m => Async a -> m ()
- uninterruptibleCancel :: MonadIO m => Async a -> m ()
- cancelWith :: (Exception e, MonadIO m) => Async a -> e -> m ()
- asyncThreadId :: Async a -> ThreadId
- waitSTM :: Async a -> STM a
- pollSTM :: Async a -> STM (Maybe (Either SomeException a))
- waitCatchSTM :: Async a -> STM (Either SomeException a)
- waitAny :: MonadIO m => [Async a] -> m (Async a, a)
- waitAnyCatch :: MonadIO m => [Async a] -> m (Async a, Either SomeException a)
- waitAnyCancel :: MonadIO m => [Async a] -> m (Async a, a)
- waitAnyCatchCancel :: MonadIO m => [Async a] -> m (Async a, Either SomeException a)
- waitEither :: MonadIO m => Async a -> Async b -> m (Either a b)
- waitEitherCatch :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEitherCancel :: MonadIO m => Async a -> Async b -> m (Either a b)
- waitEitherCatchCancel :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEither_ :: MonadIO m => Async a -> Async b -> m ()
- waitBoth :: MonadIO m => Async a -> Async 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 :: MonadIO m => Async a -> m ()
- link2 :: MonadIO m => Async a -> Async b -> m ()
- pooledMapConcurrentlyN :: (MonadUnliftIO m, Traversable t) => Int -> (a -> m b) -> t a -> m (t b)
- pooledMapConcurrently :: (MonadUnliftIO m, Traversable t) => (a -> m b) -> t a -> m (t b)
- pooledMapConcurrentlyN_ :: (MonadUnliftIO m, Foldable f) => Int -> (a -> m b) -> f a -> m ()
- pooledMapConcurrently_ :: (MonadUnliftIO m, Foldable f) => (a -> m b) -> f a -> m ()
- pooledForConcurrentlyN :: (MonadUnliftIO m, Traversable t) => Int -> t a -> (a -> m b) -> m (t b)
- pooledForConcurrently :: (MonadUnliftIO m, Traversable t) => t a -> (a -> m b) -> m (t b)
- pooledForConcurrentlyN_ :: (MonadUnliftIO m, Foldable t) => Int -> t a -> (a -> m b) -> m ()
- pooledForConcurrently_ :: (MonadUnliftIO m, Foldable f) => f a -> (a -> m b) -> m ()
- pooledReplicateConcurrentlyN :: MonadUnliftIO m => Int -> Int -> m a -> m [a]
- pooledReplicateConcurrently :: MonadUnliftIO m => Int -> m a -> m [a]
- pooledReplicateConcurrentlyN_ :: MonadUnliftIO m => Int -> Int -> m a -> m ()
- pooledReplicateConcurrently_ :: MonadUnliftIO m => Int -> m a -> m ()
- race :: MonadUnliftIO m => m a -> m b -> m (Either a b)
- race_ :: MonadUnliftIO m => m a -> m b -> m ()
- concurrently :: MonadUnliftIO m => m a -> m b -> m (a, b)
- concurrently_ :: MonadUnliftIO m => m a -> m b -> m ()
- mapConcurrently :: MonadUnliftIO m => Traversable t => (a -> m b) -> t a -> m (t b)
- forConcurrently :: MonadUnliftIO m => Traversable t => t a -> (a -> m b) -> m (t b)
- mapConcurrently_ :: MonadUnliftIO m => Foldable f => (a -> m b) -> f a -> m ()
- forConcurrently_ :: MonadUnliftIO m => Foldable f => f a -> (a -> m b) -> m ()
- replicateConcurrently :: MonadUnliftIO m => Int -> m b -> m [b]
- replicateConcurrently_ :: (Applicative m, MonadUnliftIO m) => Int -> m a -> m ()
- newtype Concurrently m a = Concurrently {- runConcurrently :: m a
 
- data Conc m a
- conc :: m a -> Conc m a
- runConc :: MonadUnliftIO m => Conc m a -> m a
- data ConcException = EmptyWithNoAlternative
- data AsyncCancelled = AsyncCancelled
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 :: MonadUnliftIO m => m a -> m (Async a) Source #
Unlifted asyncBound.
Since: 0.1.0.0
asyncWithUnmask :: MonadUnliftIO m => ((forall b. m b -> m b) -> m a) -> m (Async a) Source #
Unlifted asyncWithUnmask.
Since: 0.1.0.0
asyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async a) Source #
Unlifted asyncOnWithUnmask.
Since: 0.1.0.0
Spawning with automatic cancelation
withAsync :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b Source #
Unlifted withAsync.
Since: 0.1.0.0
withAsyncBound :: MonadUnliftIO m => m a -> (Async a -> m b) -> m b Source #
Unlifted withAsyncBound.
Since: 0.1.0.0
withAsyncOn :: MonadUnliftIO m => Int -> m a -> (Async a -> m b) -> m b Source #
Unlifted withAsyncOn.
Since: 0.1.0.0
withAsyncWithUnmask :: MonadUnliftIO m => ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b Source #
Unlifted withAsyncWithUnmask.
Since: 0.1.0.0
withAsyncOnWithUnmask :: MonadUnliftIO m => Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b Source #
Unlifted withAsyncOnWithMask.
Since: 0.1.0.0
Querying Asyncs
poll :: MonadIO m => Async a -> m (Maybe (Either SomeException a)) Source #
Lifted poll.
Since: 0.1.0.0
waitCatch :: MonadIO m => Async a -> m (Either SomeException a) Source #
Lifted waitCatch.
Since: 0.1.0.0
uninterruptibleCancel :: MonadIO m => Async a -> m () Source #
Lifted uninterruptibleCancel.
Since: 0.1.0.0
cancelWith :: (Exception e, MonadIO m) => Async a -> e -> m () Source #
Lifted cancelWith. Additionally uses toAsyncException to
 ensure async exception safety.
Since: 0.1.0.0
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
waitAnyCatch :: MonadIO m => [Async a] -> m (Async a, Either SomeException a) Source #
Lifted waitAnyCatch.
Since: 0.1.0.0
waitAnyCancel :: MonadIO m => [Async a] -> m (Async a, a) Source #
Lifted waitAnyCancel.
Since: 0.1.0.0
waitAnyCatchCancel :: MonadIO m => [Async a] -> m (Async a, Either SomeException a) Source #
Lifted waitAnyCatchCancel.
Since: 0.1.0.0
waitEither :: MonadIO m => Async a -> Async b -> m (Either a b) Source #
Lifted waitEither.
Since: 0.1.0.0
waitEitherCatch :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b)) Source #
Lifted waitEitherCatch.
Since: 0.1.0.0
waitEitherCancel :: MonadIO m => Async a -> Async b -> m (Either a b) Source #
Lifted waitEitherCancel.
Since: 0.1.0.0
waitEitherCatchCancel :: MonadIO m => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b)) Source #
Lifted waitEitherCatchCancel.
Since: 0.1.0.0
waitEither_ :: MonadIO m => Async a -> Async b -> m () Source #
Lifted waitEither_.
Since: 0.1.0.0
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
Pooled concurrency
pooledMapConcurrentlyN Source #
Arguments
| :: (MonadUnliftIO m, Traversable t) | |
| => Int | Max. number of threads. Should not be less than 1. | 
| -> (a -> m b) | |
| -> t a | |
| -> m (t b) | 
Like mapConcurrently from async, but instead of one thread per
 element, it does pooling from a set of threads. This is useful in
 scenarios where resource consumption is bounded and for use cases
 where too many concurrent tasks aren't allowed.
Example usage
import Say action :: Int -> IO Int action n = do tid <- myThreadId sayString $ show tid threadDelay (2 * 10^6) -- 2 seconds return n main :: IO () main = do yx <- pooledMapConcurrentlyN 5 (\x -> action x) [1..5] print yx
On executing you can see that five threads have been spawned:
$ ./pool ThreadId 36 ThreadId 38 ThreadId 40 ThreadId 42 ThreadId 44 [1,2,3,4,5]
Let's modify the above program such that there are less threads than the number of items in the list:
import Say action :: Int -> IO Int action n = do tid <- myThreadId sayString $ show tid threadDelay (2 * 10^6) -- 2 seconds return n main :: IO () main = do yx <- pooledMapConcurrentlyN 3 (\x -> action x) [1..5] print yx
On executing you can see that only three threads are active totally:
$ ./pool ThreadId 35 ThreadId 37 ThreadId 39 ThreadId 35 ThreadId 39 [1,2,3,4,5]
Since: 0.2.10
pooledMapConcurrently :: (MonadUnliftIO m, Traversable t) => (a -> m b) -> t a -> m (t b) Source #
Similar to pooledMapConcurrentlyN but with number of threads
 set from getNumCapabilities. Usually this is useful for CPU bound
 tasks.
Since: 0.2.10
pooledMapConcurrentlyN_ Source #
Arguments
| :: (MonadUnliftIO m, Foldable f) | |
| => Int | Max. number of threads. Should not be less than 1. | 
| -> (a -> m b) | |
| -> f a | |
| -> m () | 
Like pooledMapConcurrentlyN but with the return value
 discarded.
Since: 0.2.10
pooledMapConcurrently_ :: (MonadUnliftIO m, Foldable f) => (a -> m b) -> f a -> m () Source #
Like pooledMapConcurrently but with the return value discarded.
Since: 0.2.10
pooledForConcurrentlyN Source #
Arguments
| :: (MonadUnliftIO m, Traversable t) | |
| => Int | Max. number of threads. Should not be less than 1. | 
| -> t a | |
| -> (a -> m b) | |
| -> m (t b) | 
Similar to pooledMapConcurrentlyN but with flipped arguments.
Since: 0.2.10
pooledForConcurrently :: (MonadUnliftIO m, Traversable t) => t a -> (a -> m b) -> m (t b) Source #
Similar to pooledForConcurrentlyN but with number of threads
 set from getNumCapabilities. Usually this is useful for CPU bound
 tasks.
Since: 0.2.10
pooledForConcurrentlyN_ Source #
Arguments
| :: (MonadUnliftIO m, Foldable t) | |
| => Int | Max. number of threads. Should not be less than 1. | 
| -> t a | |
| -> (a -> m b) | |
| -> m () | 
Like pooledMapConcurrentlyN_ but with flipped arguments.
Since: 0.2.10
pooledForConcurrently_ :: (MonadUnliftIO m, Foldable f) => f a -> (a -> m b) -> m () Source #
Like pooledMapConcurrently_ but with flipped arguments.
Since: 0.2.10
pooledReplicateConcurrentlyN Source #
Arguments
| :: MonadUnliftIO m | |
| => Int | Max. number of threads. Should not be less than 1. | 
| -> Int | Number of times to perform the action. | 
| -> m a | |
| -> m [a] | 
Pooled version of replicateConcurrently. Performs the action in
 the pooled threads.
Since: 0.2.10
pooledReplicateConcurrently Source #
Arguments
| :: MonadUnliftIO m | |
| => Int | Number of times to perform the action. | 
| -> m a | |
| -> m [a] | 
Similar to pooledReplicateConcurrentlyN but with number of
 threads set from getNumCapabilities. Usually this is useful for
 CPU bound tasks.
Since: 0.2.10
pooledReplicateConcurrentlyN_ Source #
Arguments
| :: MonadUnliftIO m | |
| => Int | Max. number of threads. Should not be less than 1. | 
| -> Int | Number of times to perform the action. | 
| -> m a | |
| -> m () | 
Pooled version of replicateConcurrently_. Performs the action in
 the pooled threads.
Since: 0.2.10
pooledReplicateConcurrently_ Source #
Arguments
| :: MonadUnliftIO m | |
| => Int | Number of times to perform the action. | 
| -> m a | |
| -> m () | 
Similar to pooledReplicateConcurrently_ but with number of
 threads set from getNumCapabilities. Usually this is useful for
 CPU bound tasks.
Since: 0.2.10
Convenient utilities
race_ :: MonadUnliftIO m => m a -> m b -> m () Source #
Unlifted race_.
Since: 0.1.0.0
concurrently :: MonadUnliftIO m => m a -> m b -> m (a, b) Source #
Unlifted concurrently.
Since: 0.1.0.0
concurrently_ :: MonadUnliftIO m => m a -> m b -> m () Source #
Unlifted concurrently_.
Since: 0.1.0.0
mapConcurrently :: MonadUnliftIO m => Traversable t => (a -> m b) -> t a -> m (t b) Source #
Executes a Traversable container of items concurrently, it uses the Flat
 type internally.
Since: 0.1.0.0
forConcurrently :: MonadUnliftIO m => Traversable t => t a -> (a -> m b) -> m (t b) Source #
Similar to mapConcurrently but with arguments flipped
Since: 0.1.0.0
mapConcurrently_ :: MonadUnliftIO m => Foldable f => (a -> m b) -> f a -> m () Source #
Executes a Traversable container of items concurrently, it uses the Flat
 type internally. This function ignores the results.
Since: 0.1.0.0
forConcurrently_ :: MonadUnliftIO m => Foldable f => f a -> (a -> m b) -> m () Source #
Similar to mapConcurrently_ but with arguments flipped
Since: 0.1.0.0
replicateConcurrently :: MonadUnliftIO m => Int -> m b -> m [b] Source #
Unlifted replicateConcurrently.
Since: 0.1.0.0
replicateConcurrently_ :: (Applicative m, MonadUnliftIO m) => Int -> m a -> m () Source #
Unlifted replicateConcurrently_.
Since: 0.1.0.0
newtype Concurrently m a Source #
Unlifted Concurrently.
Since: 0.1.0.0
Constructors
| Concurrently | |
| Fields 
 | |
Instances
A more efficient alternative to Concurrently, which reduces the
 number of threads that need to be forked. For more information, see
 this blog post.
 This is provided as a separate type to Concurrently as it has a slightly different API.
Use the conc function to construct values of type Conc, and
 runConc to execute the composed actions. You can use the
 Applicative instance to run different actions and wait for all of
 them to complete, or the Alternative instance to wait for the
 first thread to complete.
In the event of a runtime exception thrown by any of the children
 threads, or an asynchronous exception received in the parent
 thread, all threads will be killed with an AsyncCancelled
 exception and the original exception rethrown. If multiple
 exceptions are generated by different threads, there are no
 guarantees on which exception will end up getting rethrown.
For many common use cases, you may prefer using helper functions in
 this module like mapConcurrently.
There are some intentional differences in behavior to
 Concurrently:
- Children threads are always launched in an unmasked state, not the inherited state of the parent thread.
Note that it is a programmer error to use the Alternative
 instance in such a way that there are no alternatives to an empty,
 e.g. runConc (empty | empty). In such a case, a ConcException
 will be thrown. If there was an Alternative in the standard
 libraries without empty, this library would use it instead.
Since: 0.2.9.0
Instances
| Functor m => Functor (Conc m) Source # | |
| MonadUnliftIO m => Applicative (Conc m) Source # | Since: 0.2.9.0 | 
| MonadUnliftIO m => Alternative (Conc m) Source # | Since: 0.2.9.0 | 
| (MonadUnliftIO m, Semigroup a) => Semigroup (Conc m a) Source # | Since: 0.2.9.0 | 
| (Monoid a, MonadUnliftIO m) => Monoid (Conc m a) Source # | Since: 0.2.9.0 | 
conc :: m a -> Conc m a Source #
Construct a value of type Conc from an action. Compose these
 values using the typeclass instances (most commonly Applicative
 and Alternative) and then run with runConc.
Since: 0.2.9.0
runConc :: MonadUnliftIO m => Conc m a -> m a Source #
Run a Conc value on multiple threads.
Since: 0.2.9.0
data ConcException Source #
Things that can go wrong in the structure of a Conc. These are
 programmer errors.
Since: 0.2.9.0
Constructors
| EmptyWithNoAlternative | 
Instances
Re-exports
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 # | |