Copyright | (c) 2016--2017 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | stable |
Portability | RankNTypes |
Safe Haskell | None |
Language | Haskell2010 |
This module is a version of the
async package. 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.
Unlike the regular async package, the Alternative
instance for
Concurrently
uses forever yield
in the definition of empty
,
rather than forever (threadDelay maxBound)
.
Synopsis
- data Async m a
- async :: MonadConc m => m a -> m (Async m a)
- asyncN :: MonadConc m => String -> m a -> m (Async m a)
- asyncBound :: MonadConc m => m a -> m (Async m a)
- asyncBoundN :: MonadConc m => String -> m a -> m (Async m a)
- asyncOn :: MonadConc m => Int -> m a -> m (Async m a)
- asyncOnN :: MonadConc m => String -> Int -> m a -> m (Async m a)
- asyncWithUnmask :: MonadConc m => ((forall b. m b -> m b) -> m a) -> m (Async m a)
- asyncWithUnmaskN :: MonadConc m => String -> ((forall b. m b -> m b) -> m a) -> m (Async m a)
- asyncOnWithUnmask :: MonadConc m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async m a)
- asyncOnWithUnmaskN :: MonadConc m => String -> Int -> ((forall b. m b -> m b) -> m a) -> m (Async m a)
- withAsync :: MonadConc m => m a -> (Async m a -> m b) -> m b
- withAsyncN :: MonadConc m => String -> m a -> (Async m a -> m b) -> m b
- withAsyncBound :: MonadConc m => m a -> (Async m a -> m b) -> m b
- withAsyncBoundN :: MonadConc m => String -> m a -> (Async m a -> m b) -> m b
- withAsyncOn :: MonadConc m => Int -> m a -> (Async m a -> m b) -> m b
- withAsyncOnN :: MonadConc m => String -> Int -> m a -> (Async m a -> m b) -> m b
- withAsyncWithUnmask :: MonadConc m => ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b
- withAsyncWithUnmaskN :: MonadConc m => String -> ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b
- withAsyncOnWithUnmask :: MonadConc m => Int -> ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b
- withAsyncOnWithUnmaskN :: MonadConc m => String -> Int -> ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b
- wait :: MonadConc m => Async m a -> m a
- waitSTM :: MonadConc m => Async m a -> STM m a
- poll :: MonadConc m => Async m a -> m (Maybe (Either SomeException a))
- pollSTM :: MonadConc m => Async m a -> STM m (Maybe (Either SomeException a))
- waitCatch :: MonadConc m => Async m a -> m (Either SomeException a)
- waitCatchSTM :: MonadConc m => Async m a -> STM m (Either SomeException a)
- cancel :: MonadConc m => Async m a -> m ()
- uninterruptibleCancel :: MonadConc m => Async m a -> m ()
- cancelWith :: (MonadConc m, Exception e) => Async m a -> e -> m ()
- asyncThreadId :: Async m a -> ThreadId m
- waitAny :: MonadConc m => [Async m a] -> m (Async m a, a)
- waitAnySTM :: MonadConc m => [Async m a] -> STM m (Async m a, a)
- waitAnyCatch :: MonadConc m => [Async m a] -> m (Async m a, Either SomeException a)
- waitAnyCatchSTM :: MonadConc m => [Async m a] -> STM m (Async m a, Either SomeException a)
- waitAnyCancel :: MonadConc m => [Async m a] -> m (Async m a, a)
- waitAnyCatchCancel :: MonadConc m => [Async m a] -> m (Async m a, Either SomeException a)
- waitEither :: MonadConc m => Async m a -> Async m b -> m (Either a b)
- waitEitherSTM :: MonadConc m => Async m a -> Async m b -> STM m (Either a b)
- waitEitherCatch :: MonadConc m => Async m a -> Async m b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEitherCatchSTM :: MonadConc m => Async m a -> Async m b -> STM m (Either (Either SomeException a) (Either SomeException b))
- waitEitherCancel :: MonadConc m => Async m a -> Async m b -> m (Either a b)
- waitEitherCatchCancel :: MonadConc m => Async m a -> Async m b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEither_ :: MonadConc m => Async m a -> Async m b -> m ()
- waitEitherSTM_ :: MonadConc m => Async m a -> Async m b -> STM m ()
- waitBoth :: MonadConc m => Async m a -> Async m b -> m (a, b)
- waitBothSTM :: MonadConc m => Async m a -> Async m b -> STM m (a, b)
- link :: MonadConc m => Async m a -> m ()
- link2 :: MonadConc m => Async m a -> Async m b -> m ()
- race :: MonadConc m => m a -> m b -> m (Either a b)
- race_ :: MonadConc m => m a -> m b -> m ()
- concurrently :: MonadConc m => m a -> m b -> m (a, b)
- concurrently_ :: MonadConc m => m a -> m b -> m ()
- mapConcurrently :: (Traversable t, MonadConc m) => (a -> m b) -> t a -> m (t b)
- mapConcurrently_ :: (Foldable f, MonadConc m) => (a -> m b) -> f a -> m ()
- forConcurrently :: (Traversable t, MonadConc m) => t a -> (a -> m b) -> m (t b)
- forConcurrently_ :: (Foldable f, MonadConc m) => f a -> (a -> m b) -> m ()
- replicateConcurrently :: MonadConc m => Int -> m a -> m [a]
- replicateConcurrently_ :: MonadConc m => Int -> m a -> m ()
- newtype Concurrently m a = Concurrently {
- runConcurrently :: m a
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
).
Note that, unlike the "async" package, Async
here does not have
an Ord
instance. This is because MonadConc
ThreadId
s do not
necessarily have one.
Since: 1.1.1.0
Spawning
async :: MonadConc m => m a -> m (Async m a) Source #
Spawn an asynchronous action in a separate thread.
Since: 1.1.1.0
asyncN :: MonadConc m => String -> m a -> m (Async m a) Source #
Like async
, but using a named thread for better debugging information.
Since: 1.2.1.0
asyncBound :: MonadConc m => m a -> m (Async m a) Source #
asyncBoundN :: MonadConc m => String -> m a -> m (Async m a) Source #
Like asyncBound
, but using a named thread for better debugging
information.
Since: 1.3.0.0
asyncOnN :: MonadConc m => String -> Int -> m a -> m (Async m a) Source #
Like asyncOn
but using a named thread for better debugging information.
Since: 1.2.1.0
asyncWithUnmask :: MonadConc m => ((forall b. m b -> m b) -> m a) -> m (Async m a) Source #
Like async
but using forkWithUnmask
internally.
Since: 1.1.1.0
asyncWithUnmaskN :: MonadConc m => String -> ((forall b. m b -> m b) -> m a) -> m (Async m a) Source #
Like asyncWithUnmask
but using a named thread for better debugging information.
Since: 1.2.1.0
asyncOnWithUnmask :: MonadConc m => Int -> ((forall b. m b -> m b) -> m a) -> m (Async m a) Source #
Like asyncOn
but using forkOnWithUnmask
internally.
Since: 1.1.1.0
asyncOnWithUnmaskN :: MonadConc m => String -> Int -> ((forall b. m b -> m b) -> m a) -> m (Async m a) Source #
Like asyncOnWithUnmask
but using a named thread for better debugging information.
Since: 1.2.1.0
Spawning with automatic cancel
ation
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, uninterruptibleCancel
is called on the Async
.
withAsync action inner = bracket (async action) uninterruptiblCancel inner
This is a useful variant of async
that ensures an Async
is
never left running unintentionally.
Since uninterruptibleCancel
may block, withAsync
may also
block; see uninterruptibleCancel
for details.
Since: 1.1.1.0
withAsyncN :: MonadConc m => String -> m a -> (Async m a -> m b) -> m b Source #
Like withAsync
but using a named thread for better debugging
information.
Since: 1.2.3.0
withAsyncBound :: MonadConc m => m a -> (Async m a -> m b) -> m b Source #
withAsyncBoundN :: MonadConc m => String -> m a -> (Async m a -> m b) -> m b Source #
Like withAsyncBound
but using a named thread for better
debugging information.
Since: 1.3.0.0
withAsyncOnN :: MonadConc m => String -> Int -> m a -> (Async m a -> m b) -> m b Source #
Like withAsyncOn
but using a named thread for better debugging
information.
Since: 1.2.3.0
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.
Since: 1.1.1.0
withAsyncWithUnmaskN :: MonadConc m => String -> ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b Source #
Like withAsyncWithUnmask
but using a named thread for better
debugging information.
Since: 1.2.3.0
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.
Since: 1.1.1.0
withAsyncOnWithUnmaskN :: MonadConc m => String -> Int -> ((forall x. m x -> m x) -> m a) -> (Async m a -> m b) -> m b Source #
Like withAsyncOnWithUnmask
but using a named thread for better
debugging information.
Since: 1.2.3.0
Querying Async
s
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
Since: 1.1.1.0
waitSTM :: MonadConc m => Async m a -> STM m a Source #
A version of wait
that can be used inside a MonadSTM
transaction.
Since: 1.1.1.0
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
Since: 1.1.1.0
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.
Since: 1.1.1.0
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
.
Since: 1.1.1.0
waitCatchSTM :: MonadConc m => Async m a -> STM m (Either SomeException a) Source #
A version of waitCatch
that can be used inside a MonadSTM
transaction.
Since: 1.1.1.0
cancel :: MonadConc m => Async m a -> m () Source #
Cancel an asynchronous action by throwing the ThreadKilled
exception to it, and waiting for the Async
thread to quit. Has no
effect if the Async
has already completed.
cancel a = throwTo (asyncThreadId a) ThreadKilled <* waitCatch a
Note that cancel
will not terminate until the thread the Async
refers to has terminated. This means that cancel
will block for
as long as said thread blocks when receiving an asynchronous
exception.
An asynchronous cancel
can of course be obtained by wrapping
cancel
itself in async
.
Since: 1.1.1.0
uninterruptibleCancel :: MonadConc m => Async m a -> m () Source #
Cancel an asynchronous action.
This is a variant of cancel
but it is not interruptible.
Since: 1.1.2.0
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
.
Since: 1.1.1.0
asyncThreadId :: Async m a -> ThreadId m Source #
Waiting for multiple Async
s
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.
Since: 1.1.1.0
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 Async
s complete or have completed, then the value
returned corresponds to the first completed Async
in the list.
Since: 1.1.1.0
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.
Since: 1.1.1.0
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.
Since: 1.1.1.0
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.
Since: 1.1.1.0
waitEither :: MonadConc m => Async m a -> Async m b -> m (Either a b) Source #
Wait for the first of two Async
s to finish. If the Async
that finished first raised an exception, then the exception is
re-thrown by waitEither
.
Since: 1.1.1.0
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.
Since: 1.1.1.0
waitEitherCatch :: MonadConc m => Async m a -> Async m b -> m (Either (Either SomeException a) (Either SomeException b)) Source #
Wait for the first of two Async
s to finish.
Since: 1.1.1.0
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.
Since: 1.1.1.0
waitEitherCancel :: MonadConc m => Async m a -> Async m b -> m (Either a b) Source #
Like waitEither
, but also cancel
s both Async
s before
returning.
Since: 1.1.1.0
waitEitherCatchCancel :: MonadConc m => Async m a -> Async m b -> m (Either (Either SomeException a) (Either SomeException b)) Source #
Like waitEitherCatch
, but also cancel
s both Async
s before
returning.
Since: 1.1.1.0
waitEither_ :: MonadConc m => Async m a -> Async m b -> m () Source #
Like waitEither
, but the result is ignored.
Since: 1.1.1.0
waitEitherSTM_ :: MonadConc m => Async m a -> Async m b -> STM m () Source #
A version of waitEither_
that can be used inside a MonadSTM
transaction.
Since: 1.1.1.0
waitBoth :: MonadConc m => Async m a -> Async m b -> m (a, b) Source #
Waits for both Async
s to finish, but if either of them throws
an exception before they have both finished, then the exception is
re-thrown by waitBoth
.
Since: 1.1.1.0
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.
Since: 1.1.1.0
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.
Since: 1.1.1.0
link2 :: MonadConc m => Async m a -> Async m b -> m () Source #
Link two Async
s together, such that if either raises an
exception, the same exception is re-thrown in the other Async
.
Since: 1.1.1.0
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 cancel
led.
race left right = withAsync left $ \a -> withAsync right $ \b -> waitEither a b
Since: 1.1.1.0
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
Since: 1.1.1.0
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 cancel
led, and the exception is re-thrown by
concurrently
.
concurrently left right = withAsync left $ \a -> withAsync right $ \b -> waitBoth a b
Since: 1.1.1.0
concurrently_ :: MonadConc m => m a -> m b -> m () Source #
concurrently_
is concurrently
but ignores the return values.
Since: 1.1.2.0
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"]
Since: 1.1.1.0
mapConcurrently_ :: (Foldable f, MonadConc m) => (a -> m b) -> f a -> m () Source #
mapConcurrently_
is mapConcurrently
with the return value
discarded, just like mapM_
.
Since: 1.1.2.0
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
Since: 1.1.1.0
forConcurrently_ :: (Foldable f, MonadConc m) => f a -> (a -> m b) -> m () Source #
forConcurrently_
is forConcurrently
with the return value
discarded, just like forM_
.
Since: 1.1.2.0
replicateConcurrently :: MonadConc m => Int -> m a -> m [a] Source #
Perform the action in the given number of threads.
Since: 1.1.2.0
replicateConcurrently_ :: MonadConc m => Int -> m a -> m () Source #
replicateConcurrently_
is replicateConcurrently
with the
return values discarded.
Since: 1.1.2.0
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")
Since: 1.1.1.0
Concurrently | |
|