unliftio-0.2.9.0: The MonadUnliftIO typeclass for unlifting monads to IO (batteries included)

Safe HaskellNone
LanguageHaskell2010

UnliftIO.Async

Contents

Description

Unlifted Control.Concurrent.Async.

Since: 0.1.0.0

Synopsis

Asynchronous actions

data Async a #

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

Defined in Control.Concurrent.Async

Methods

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

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

Eq (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

(==) :: Async a -> Async a -> Bool #

(/=) :: Async a -> Async a -> Bool #

Ord (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

compare :: Async a -> Async a -> Ordering #

(<) :: Async a -> Async a -> Bool #

(<=) :: Async a -> Async a -> Bool #

(>) :: Async a -> Async a -> Bool #

(>=) :: Async a -> Async a -> Bool #

max :: Async a -> Async a -> Async a #

min :: Async a -> Async a -> Async a #

Hashable (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

hashWithSalt :: Int -> Async a -> Int #

hash :: Async a -> Int #

Spawning

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

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

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

asyncThreadId :: Async a -> ThreadId #

Returns the ThreadId of the thread running the given Async.

STM operations

waitSTM :: Async a -> STM a #

A version of wait that can be used inside an STM transaction.

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

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

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

Convenient utilities

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

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

data Conc m a Source #

A more efficient alternative to Concurrently, which reduces the number of threads that need to be forked. For more information, see FIXME link to 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 # 
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

data ConcException Source #

Things that can go wrong in the structure of a Conc. These are programmer errors.

Since: 0.2.9.0

Instances
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.9.0-8hp3YwMM3GB2T15X1aYWey" False) (C1 (MetaCons "EmptyWithNoAlternative" PrefixI False) (U1 :: Type -> Type))