async-dejafu-0.1.2.0: Run MonadConc operations asynchronously and wait for their results.

Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.Async

Contents

Description

This module is a version of the async package using the dejafu concurrency abstraction. It provides a set of operations for running MonadConc operations asynchronously and waiting for their results.

For example, assuming a suitable getURL function, we can fetch the contents of two web pages at the same time:

withAsync (getURL url1) $ \a1 -> do
withAsync (getURL url2) $ \a2 -> do
page1 <- wait a1
page2 <- wait a2
...

The withAsync function starts an operation in a separate thread, and kills it if the inner action finishes before it completes.

There are a few deviations from the regular async package:

  • asyncBound and withAsyncBound are missing as dejafu does not support bound threads.
  • The Alternative instance for Concurrently uses forever yield in the definition of empty, rather than forever (threadDelay maxBound).

Synopsis

Asynchronous actions

data Async m a Source

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

Note that, unlike the "async" package, Async here does not have an Ord instance. This is because MonadConc ThreadIds do not necessarily have one.

Instances

Spawning

async :: MonadConc m => m a -> m (Async m a) Source

Spawn an asynchronous action in a separate thread.

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

Like async but using forkOn internally.

asyncWithUnmask :: MonadConc m => ((forall b. m b -> m b) -> m a) -> m (Async m a) Source

Like async but using forkWithUnmask internally.

asyncOnWithUnmask :: MonadConc m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async m a) Source

Like asyncOn but using forkOnWithUnmask internally.

Spawning with automatic cancelation

withAsync :: MonadConc m => m a -> (Async m a -> m b) -> m b Source

Spawn an asynchronous action in a separate thread, and pass its Async handle to the supplied function. When the function returns or throws an exception, cancel is called on the Async.

withAsync action inner = bracket (async action) cancel inner

This is a useful variant of async that ensures an Async is never left running unintentionally.

Since cancel may block, withAsync may also block; see cancel for details.

withAsyncOn :: MonadConc m => Int -> m a -> (Async m a -> m b) -> m b Source

Like withAsync but uses forkOn internally.

withAsyncWithUnmask :: MonadConc m => ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b Source

Like withAsync bit uses forkWithUnmask internally.

withAsyncOnWithUnmask :: MonadConc m => Int -> ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b Source

Like withAsyncOn bit uses forkOnWithUnmask internally.

Querying Asyncs

wait :: MonadConc m => Async m a -> m a Source

Wait for an asynchronous action to complete, and return its value. If the asynchronous value threw an exception, then the exception is re-thrown by wait.

wait = atomically . waitSTM

waitSTM :: MonadConc m => Async m a -> STM m a Source

A version of wait that can be used inside a MonadSTM transaction.

poll :: MonadConc m => Async m a -> m (Maybe (Either SomeException a)) Source

Check whether an Async has completed yet. If it has not completed yet, then the result is Nothing, otherwise the result is Just e where e is Left x if the Async raised an exception x, or Right a if it returned a value a.

poll = atomically . pollSTM

pollSTM :: MonadConc m => Async m a -> STM m (Maybe (Either SomeException a)) Source

A version of poll that can be used inside a MonadSTM transaction.

waitCatch :: MonadConc m => Async m a -> m (Either SomeException a) Source

Wait for an asynchronous action to complete, and return either Left e if the action raised an exception e, or Right a if it returned a value a.

waitCatchSTM :: MonadConc m => Async m a -> STM m (Either SomeException a) Source

A version of waitCatch that can be used inside a MonadSTM transaction.

cancel :: MonadConc m => Async m a -> m () Source

Cancel an asynchronous action by throwing the ThreadKilled exception to it. Has no effect if the Async has already completed.

cancel a = throwTo (asyncThreadId a) ThreadKilled

Note that cancel is synchronous in the same sense as throwTo. It does not return until the exception has been thrown in the target thread, or the target thread has completed. An asynchronous cancel can of course be obtained by wrapping cancel itself in async.

cancelWith :: (MonadConc m, Exception e) => Async m a -> e -> m () Source

Cancel an asynchronous action by throwing the supplied exception to it.

cancelWith a e = throwTo (asyncThreadId a) e

The notes about the synchronous nature of cancel also apply to cancelWith.

Waiting for multiple Asyncs

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

Wait for any of the supplied Asyncs to complete. If the first to complete throws an exception, then that exception is re-thrown by waitAny.

If multiple Asyncs complete or have completed, then the value returned corresponds to the first completed Async in the list.

waitAnySTM :: MonadConc m => [Async m a] -> STM m (Async m a, a) Source

A version of waitAny that can be used inside a MonadSTM transaction.

waitAnyCatch :: MonadConc m => [Async m a] -> m (Async m a, Either SomeException a) Source

Wait for any of the supplied asynchronous operations to complete. The value returned is a pair of the Async that completed, and the result that would be returned by wait on that Async.

If multiple Asyncs complete or have completed, then the value returned corresponds to the first completed Async in the list.

waitAnyCatchSTM :: MonadConc m => [Async m a] -> STM m (Async m a, Either SomeException a) Source

A version of waitAnyCatch that can be used inside a MonadSTM transaction.

waitAnyCancel :: MonadConc m => [Async m a] -> m (Async m a, a) Source

Like waitAny, but also cancels the other asynchronous operations as soon as one has completed.

waitAnyCatchCancel :: MonadConc m => [Async m a] -> m (Async m a, Either SomeException a) Source

Like waitAnyCatch, but also cancels the other asynchronous operations as soon as one has completed.

waitEither :: MonadConc m => Async m a -> Async m b -> m (Either a b) Source

Wait for the first of two Asyncs to finish. If the Async that finished first raised an exception, then the exception is re-thrown by waitEither.

waitEitherSTM :: MonadConc m => Async m a -> Async m b -> STM m (Either a b) Source

A version of waitEither that can be used inside a MonadSTM transaction.

waitEitherCatch :: MonadConc m => Async m a -> Async m b -> m (Either (Either SomeException a) (Either SomeException b)) Source

Wait for the first of two Asyncs to finish.

waitEitherCatchSTM :: MonadConc m => Async m a -> Async m b -> STM m (Either (Either SomeException a) (Either SomeException b)) Source

A version of waitEitherCatch that can be used inside a MonadSTM transaction.

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

Like waitEither, but also cancels both Asyncs before returning.

waitEitherCatchCancel :: MonadConc m => Async m a -> Async m b -> m (Either (Either SomeException a) (Either SomeException b)) Source

Like waitEitherCatch, but also cancels both Asyncs before returning.

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

Like waitEither, but the result is ignored.

waitEitherSTM_ :: MonadConc m => Async m a -> Async m b -> STM m () Source

A version of waitEither_ that can be used inside a MonadSTM transaction.

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

Waits for both Asyncs to finish, but if either of them throws an exception before they have both finished, then the exception is re-thrown by waitBoth.

waitBothSTM :: MonadConc m => Async m a -> Async m b -> STM m (a, b) Source

A version of waitBoth that can be used inside a MonadSTM transaction.

Linking

link :: MonadConc m => Async m a -> m () Source

Link the given Async to the current thread, such that if the Async raises an exception, that exception will be re-thrown in the current thread.

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

Link two Asyncs together, such that if either raises an exception, the same exception is re-thrown in the other Async.

Convenient utilities

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

Run two MonadConc actions concurrently, and return the first to finish. The loser of the race is cancelled.

race left right =
  withAsync left $ \a ->
  withAsync right $ \b ->
  waitEither a b

race_ :: MonadConc m => m a -> m b -> m () Source

Like race, but the result is ignored.

race_ left right =
  withAsync left $ \a ->
  withAsync right $ \b ->
  waitEither_ a b

concurrently :: MonadConc m => m a -> m b -> m (a, b) Source

Run two MonadConc actions concurrently, and return both results. If either action throws an exception at any time, then the other action is cancelled, and the exception is re-thrown by concurrently.

concurrently left right =
  withAsync left $ \a ->
  withAsync right $ \b ->
  waitBoth a b

mapConcurrently :: (Traversable t, MonadConc m) => (a -> m b) -> t a -> m (t b) Source

Maps a MonadConc-performing function over any Traversable data type, performing all the MonadConc actions concurrently, and returning the original data structure with the arguments replaced by the results.

For example, mapConcurrently works with lists:

pages <- mapConcurrently getURL ["url1", "url2", "url3"]

forConcurrently :: (Traversable t, MonadConc m) => t a -> (a -> m b) -> m (t b) Source

forConcurrently is mapConcurrently with its arguments flipped

pages <- forConcurrently ["url1", "url2", "url3"] $ \url -> getURL url

newtype Concurrently m a Source

A value of type Concurrently m a is a MonadConc operation that can be composed with other Concurrently values, using the Applicative and Alternative instances.

Calling runConcurrently on a value of type Concurrently m a will execute the MonadConc operations it contains concurrently, before delivering the result of type a.

For example

(page1, page2, page3)
  <- runConcurrently $ (,,)
  <$> Concurrently (getURL "url1")
  <*> Concurrently (getURL "url2")
  <*> Concurrently (getURL "url3")

Constructors

Concurrently 

Fields

runConcurrently :: m a