unliftio-0.2.22.0: The MonadUnliftIO typeclass for unlifting monads to IO (batteries included)
Safe HaskellNone
LanguageHaskell2010

UnliftIO.Internals.Async

Synopsis

Documentation

async :: MonadUnliftIO m => m a -> m (Async a) Source #

Unlifted async.

Since: 0.1.0.0

asyncBound :: MonadUnliftIO m => m a -> m (Async a) Source #

Unlifted asyncBound.

Since: 0.1.0.0

asyncOn :: MonadUnliftIO m => Int -> m a -> m (Async a) Source #

Unlifted asyncOn.

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

wait :: MonadIO m => Async a -> m a Source #

Lifted wait.

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

cancel :: MonadIO m => Async a -> m () Source #

Lifted cancel.

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

waitAny :: MonadIO m => [Async a] -> m (Async a, a) Source #

Lifted waitAny.

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

waitEitherCancel :: MonadIO m => Async a -> Async b -> m (Either a b) Source #

Lifted waitEitherCancel.

Since: 0.1.0.0

waitEither_ :: MonadIO m => Async a -> Async b -> m () Source #

Lifted waitEither_.

Since: 0.1.0.0

waitBoth :: MonadIO m => Async a -> Async b -> m (a, b) Source #

Lifted waitBoth.

Since: 0.1.0.0

link :: MonadIO m => Async a -> m () Source #

Lifted link.

Since: 0.1.0.0

link2 :: MonadIO m => Async a -> Async b -> m () Source #

Lifted link2.

Since: 0.1.0.0

race :: MonadUnliftIO m => m a -> m b -> m (Either a b) Source #

Unlifted race.

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

Constructors

Concurrently 

Fields

Instances

Instances details
Monad m => Functor (Concurrently m) Source #

Since: 0.1.0.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

fmap :: (a -> b) -> Concurrently m a -> Concurrently m b #

(<$) :: a -> Concurrently m b -> Concurrently m a #

MonadUnliftIO m => Applicative (Concurrently m) Source #

Since: 0.1.0.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> Concurrently m a #

(<*>) :: Concurrently m (a -> b) -> Concurrently m a -> Concurrently m b #

liftA2 :: (a -> b -> c) -> Concurrently m a -> Concurrently m b -> Concurrently m c #

(*>) :: Concurrently m a -> Concurrently m b -> Concurrently m b #

(<*) :: Concurrently m a -> Concurrently m b -> Concurrently m a #

MonadUnliftIO m => Alternative (Concurrently m) Source #

Composing two unlifted Concurrently values using Alternative is the equivalent to using a race combinator, the asynchrounous sub-routine that returns a value first is the one that gets it's value returned, the slowest sub-routine gets cancelled and it's thread is killed.

Since: 0.1.0.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

empty :: Concurrently m a #

(<|>) :: Concurrently m a -> Concurrently m a -> Concurrently m a #

some :: Concurrently m a -> Concurrently m [a] #

many :: Concurrently m a -> Concurrently m [a] #

(MonadUnliftIO m, Semigroup a) => Semigroup (Concurrently m a) Source #

Only defined by async for base >= 4.9.

Since: 0.1.0.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

(<>) :: Concurrently m a -> Concurrently m a -> Concurrently m a #

sconcat :: NonEmpty (Concurrently m a) -> Concurrently m a #

stimes :: Integral b => b -> Concurrently m a -> Concurrently m a #

(Semigroup a, Monoid a, MonadUnliftIO m) => Monoid (Concurrently m a) Source #

Since: 0.1.0.0

Instance details

Defined in UnliftIO.Internals.Async

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 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

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

data Conc m a where Source #

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

Constructors

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

Instances details
Functor m => Functor (Conc m) Source # 
Instance details

Defined in UnliftIO.Internals.Async

Methods

fmap :: (a -> b) -> Conc m a -> Conc m b #

(<$) :: a -> Conc m b -> Conc m a #

MonadUnliftIO m => Applicative (Conc m) Source #

Since: 0.2.9.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> Conc m a #

(<*>) :: Conc m (a -> b) -> Conc m a -> Conc m b #

liftA2 :: (a -> b -> c) -> Conc m a -> Conc m b -> Conc m c #

(*>) :: Conc m a -> Conc m b -> Conc m b #

(<*) :: Conc m a -> Conc m b -> Conc m a #

MonadUnliftIO m => Alternative (Conc m) Source #

Since: 0.2.9.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

empty :: Conc m a #

(<|>) :: Conc m a -> Conc m a -> Conc m a #

some :: Conc m a -> Conc m [a] #

many :: Conc m a -> Conc m [a] #

(MonadUnliftIO m, Semigroup a) => Semigroup (Conc m a) Source #

Since: 0.2.9.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

(<>) :: Conc m a -> Conc m a -> Conc m a #

sconcat :: NonEmpty (Conc m a) -> Conc m a #

stimes :: Integral b => b -> Conc m a -> Conc m a #

(Monoid a, MonadUnliftIO m) => Monoid (Conc m a) Source #

Since: 0.2.9.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

mempty :: Conc m a #

mappend :: Conc m a -> Conc m a -> Conc m a #

mconcat :: [Conc m a] -> Conc m a #

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.

data Flat a Source #

Flattened structure, either Applicative or Alternative

Constructors

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).

Instances

Instances details
Functor Flat Source # 
Instance details

Defined in UnliftIO.Internals.Async

Methods

fmap :: (a -> b) -> Flat a -> Flat b #

(<$) :: a -> Flat b -> Flat a #

Applicative Flat Source # 
Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> Flat a #

(<*>) :: Flat (a -> b) -> Flat a -> Flat b #

liftA2 :: (a -> b -> c) -> Flat a -> Flat b -> Flat c #

(*>) :: Flat a -> Flat b -> Flat b #

(<*) :: Flat a -> Flat b -> Flat a #

data FlatApp a where Source #

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

Constructors

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 

Instances

Instances details
Functor FlatApp Source # 
Instance details

Defined in UnliftIO.Internals.Async

Methods

fmap :: (a -> b) -> FlatApp a -> FlatApp b #

(<$) :: a -> FlatApp b -> FlatApp a #

Applicative FlatApp Source # 
Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> FlatApp a #

(<*>) :: FlatApp (a -> b) -> FlatApp a -> FlatApp b #

liftA2 :: (a -> b -> c) -> FlatApp a -> FlatApp b -> FlatApp c #

(*>) :: FlatApp a -> FlatApp b -> FlatApp b #

(<*) :: FlatApp a -> FlatApp b -> 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

Instances details
Eq ConcException Source # 
Instance details

Defined in UnliftIO.Internals.Async

Ord ConcException Source # 
Instance details

Defined in UnliftIO.Internals.Async

Show ConcException Source # 
Instance details

Defined in UnliftIO.Internals.Async

Generic ConcException Source # 
Instance details

Defined in UnliftIO.Internals.Async

Associated Types

type Rep ConcException :: Type -> Type #

Exception ConcException Source # 
Instance details

Defined in UnliftIO.Internals.Async

type Rep ConcException Source # 
Instance details

Defined in UnliftIO.Internals.Async

type Rep ConcException = D1 ('MetaData "ConcException" "UnliftIO.Internals.Async" "unliftio-0.2.22.0-8XX2qytUiYHJDqmPuk7olC" 'False) (C1 ('MetaCons "EmptyWithNoAlternative" 'PrefixI 'False) (U1 :: Type -> Type))

type DList a = [a] -> [a] Source #

Simple difference list, for nicer types below

dlistCons :: a -> DList a -> DList a Source #

flatten :: forall m a. MonadUnliftIO m => Conc m a -> m (Flat a) Source #

Turn a Conc into a Flat. Note that thanks to the ugliness of empty, this may fail, e.g. flatten Empty.

Since: 0.2.9.0

runFlat :: Flat a -> IO a Source #

Run a Flat a on multiple threads.

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

Expand
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 #

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

pooledMapConcurrentlyIO :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b) Source #

pooledConcurrently Source #

Arguments

:: 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 #

Arguments

:: Traversable t 
=> Int

Max. number of threads. Should not be less than 1.

-> (a -> IO b) 
-> t a 
-> IO (t b) 

pooledMapConcurrentlyIO_' :: Foldable t => Int -> (a -> IO ()) -> t a -> IO () Source #

pooledMapConcurrentlyIO_ :: Foldable t => Int -> (a -> IO b) -> t a -> IO () Source #

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

pooledForConcurrently_ :: (MonadUnliftIO m, Foldable f) => f a -> (a -> m b) -> m () Source #

Like pooledMapConcurrently_ but with flipped arguments.

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

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