Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- 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 ()
- 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)
- link :: MonadIO m => Async a -> m ()
- link2 :: MonadIO m => Async a -> Async b -> 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 ()
- newtype Concurrently m a = Concurrently {
- runConcurrently :: m a
- forConcurrently :: MonadUnliftIO m => Traversable t => t a -> (a -> m b) -> m (t b)
- forConcurrently_ :: MonadUnliftIO m => Foldable f => f a -> (a -> m b) -> m ()
- replicateConcurrently :: MonadUnliftIO f => Int -> f a -> f [a]
- replicateConcurrently_ :: (Applicative m, MonadUnliftIO m) => Int -> m a -> m ()
- mapConcurrently :: MonadUnliftIO m => Traversable t => (a -> m b) -> t a -> m (t b)
- mapConcurrently_ :: MonadUnliftIO m => Foldable f => (a -> m b) -> f a -> m ()
- data Conc m a where
- conc :: m a -> Conc m a
- runConc :: MonadUnliftIO m => Conc m a -> m a
- data Flat a
- data FlatApp a where
- data ConcException = EmptyWithNoAlternative
- type DList a = [a] -> [a]
- dlistConcat :: DList a -> DList a -> DList a
- dlistCons :: a -> DList a -> DList a
- dlistConcatAll :: [DList a] -> DList a
- dlistToList :: DList a -> [a]
- dlistSingleton :: a -> DList a
- dlistEmpty :: DList a
- flatten :: forall m a. MonadUnliftIO m => Conc m a -> m (Flat a)
- runFlat :: Flat a -> IO a
- 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)
- 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)
- pooledMapConcurrentlyIO :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b)
- pooledConcurrently :: Int -> IORef [a] -> (a -> IO ()) -> IO ()
- pooledMapConcurrentlyIO' :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b)
- pooledMapConcurrentlyIO_' :: Foldable t => Int -> (a -> IO ()) -> t a -> IO ()
- pooledMapConcurrentlyIO_ :: Foldable t => Int -> (a -> IO b) -> t a -> IO ()
- pooledMapConcurrentlyN_ :: (MonadUnliftIO m, Foldable f) => Int -> (a -> m b) -> f a -> m ()
- pooledMapConcurrently_ :: (MonadUnliftIO m, Foldable f) => (a -> m b) -> f a -> m ()
- pooledForConcurrently_ :: (MonadUnliftIO m, Foldable f) => f a -> (a -> m b) -> m ()
- pooledForConcurrentlyN_ :: (MonadUnliftIO m, Foldable t) => Int -> t 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 ()
Documentation
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
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
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
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
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
newtype Concurrently m a Source #
Unlifted Concurrently
.
Since: 0.1.0.0
Concurrently | |
|
Instances
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
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 f => Int -> f a -> f [a] 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
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
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
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
Action :: m a -> Conc m a | |
Apply :: Conc m (v -> a) -> Conc m v -> Conc m a | |
LiftA2 :: (x -> y -> a) -> Conc m x -> Conc m y -> Conc m a | |
Pure :: a -> Conc m a | |
Alt :: Conc m a -> Conc m a -> Conc m a | |
Empty :: Conc m a |
Instances
MonadUnliftIO m => Alternative (Conc m) Source # | Since: 0.2.9.0 |
MonadUnliftIO m => Applicative (Conc m) Source # | Since: 0.2.9.0 |
Functor m => Functor (Conc m) Source # | |
(Monoid a, MonadUnliftIO m) => Monoid (Conc m a) Source # | Since: 0.2.9.0 |
(MonadUnliftIO m, Semigroup a) => Semigroup (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
We want to get rid of the Empty data constructor. We don't want
We want to ensure that there is no nesting of Alt data
We want to ensure that, when racing, we're always racing at least
We want to simplify down to IO.
Flattened structure, either Applicative or Alternative
FlatApp !(FlatApp a) | |
FlatAlt !(FlatApp a) !(FlatApp a) ![FlatApp a] | Flattened Alternative. Has at least 2 entries, which must be FlatApp (no nesting of FlatAlts). |
Flattened Applicative. No Alternative stuff directly in here, but may be in the children. Notice this type doesn't have a type parameter for monadic contexts, it hardwires the base monad to IO given concurrency relies eventually on that.
Since: 0.2.9.0
FlatPure :: a -> FlatApp a | |
FlatAction :: IO a -> FlatApp a | |
FlatApply :: Flat (v -> a) -> Flat v -> FlatApp a | |
FlatLiftA2 :: (x -> y -> a) -> Flat x -> Flat y -> FlatApp a |
data ConcException Source #
Things that can go wrong in the structure of a Conc
. These are
programmer errors.
Since: 0.2.9.0
Instances
dlistConcatAll :: [DList a] -> DList a Source #
dlistToList :: DList a -> [a] Source #
dlistSingleton :: a -> DList a Source #
dlistEmpty :: DList a Source #
pooledMapConcurrentlyN Source #
:: (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
pooledForConcurrentlyN Source #
:: (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
pooledMapConcurrentlyIO :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b) Source #
:: Int | Max. number of threads. Should not be less than 1. |
-> IORef [a] | Task queue. These are required as inputs for the jobs. |
-> (a -> IO ()) | The task which will be run concurrently (but will be pooled properly). |
-> IO () |
Performs the actual pooling for the tasks. This function will continue execution until the task queue becomes empty. When one of the pooled thread finishes it's task, it will pickup the next task from the queue if an job is available.
pooledMapConcurrentlyIO' Source #
:: Traversable t | |
=> Int | Max. number of threads. Should not be less than 1. |
-> (a -> IO b) | |
-> t a | |
-> IO (t b) |
pooledMapConcurrentlyN_ Source #
:: (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
pooledForConcurrently_ :: (MonadUnliftIO m, Foldable f) => f a -> (a -> m b) -> m () Source #
Like pooledMapConcurrently_
but with flipped arguments.
Since: 0.2.10
pooledForConcurrentlyN_ Source #
:: (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
pooledReplicateConcurrentlyN Source #
:: 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 #
:: 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 #
:: 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 #
:: 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