lifted-async-0.7.0: Run lifted IO operations asynchronously and wait for their results

CopyrightCopyright (C) 2012-2015 Mitsutoshi Aoe
LicenseBSD-style (see the file LICENSE)
MaintainerMitsutoshi Aoe <maoe@foldr.in>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Control.Concurrent.Async.Lifted.Safe

Contents

Description

This is a safe variant of Control.Concurrent.Async.Lifted.

This module assumes your monad stack to satisfy StM m a ~ a so you can't mess up monadic effects. If your monad stack is stateful, use Control.Concurrent.Async.Lifted with special care.

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

class (StM m a ~ a) => Pure m a Source

Most of the functions in this module have Forall (Pure m) in their constraints, which means they require the monad m satisfies StM m a ~ a for all a.

Instances

(~) * (StM m a) a => Pure m a 

type Forall p = (p A, p B)

A quantified constraint

Spawning

async :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m (Async a) Source

Generalized version of async.

asyncBound :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m (Async a) Source

Generalized version of asyncBound.

asyncOn :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> m (Async a) Source

Generalized version of asyncOn.

asyncWithUnmask :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => ((forall b. m b -> m b) -> m a) -> m (Async a) Source

Generalized version of asyncWithUnmask.

asyncOnWithUnmask :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => Int -> ((forall b. m b -> m b) -> m a) -> m (Async a) Source

Generalized version of asyncOnWithUnmask.

Spawning with automatic cancelation

withAsync :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> (Async a -> m b) -> m b Source

Generalized version of withAsync.

withAsyncBound :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> (Async a -> m b) -> m b Source

Generalized version of withAsyncBound.

withAsyncOn :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> (Async a -> m b) -> m b Source

Generalized version of withAsyncOn.

withAsyncWithUnmask :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b Source

Generalized version of withAsyncWithUnmask.

withAsyncOnWithUnmask :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Int -> ((forall c. m c -> m c) -> m a) -> (Async a -> m b) -> m b Source

Generalized version of withAsyncOnWithUnmask.

Quering Asyncs

wait :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> m a Source

Generalized version of wait.

poll :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> m (Maybe (Either SomeException a)) Source

Generalized version of poll.

waitCatch :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> m (Either SomeException a) Source

Generalized version of waitCatch.

cancel :: MonadBase IO m => Async a -> m () Source

Generalized version of cancel.

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

Generalized version of cancelWith.

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 :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => [Async a] -> m (Async a, a) Source

Generalized version of waitAny.

waitAnyCatch :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => [Async a] -> m (Async a, Either SomeException a) Source

Generalized version of waitAnyCatch.

waitAnyCancel :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => [Async a] -> m (Async a, a) Source

Generalized version of waitAnyCancel.

waitAnyCatchCancel :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => [Async a] -> m (Async a, Either SomeException a) Source

Generalized version of waitAnyCatchCancel.

waitEither :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> Async b -> m (Either a b) Source

Generalized version of waitEither.

waitEitherCatch :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b)) Source

Generalized version of waitEitherCatch.

waitEitherCancel :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> Async b -> m (Either a b) Source

Generalized version of waitEitherCancel.

waitEitherCatchCancel :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b)) Source

Generalized version of waitEitherCatchCancel.

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

Generalized version of waitEither_.

NOTE: This function discards the monadic effects besides IO in the forked computation.

waitBoth :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Async a -> Async b -> m (a, b) Source

Generalized version of waitBoth.

Linking

link :: MonadBase IO m => Async a -> m () Source

Generalized version of link.

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

Generalized version of link2.

Convenient utilities

race :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m (Either a b) Source

Generalized version of race.

race_ :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m () Source

Generalized version of race_.

concurrently :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m (a, b) Source

Generalized version of concurrently.

mapConcurrently :: (Traversable t, MonadBaseControl IO m, Forall (Pure m)) => (a -> m b) -> t a -> m (t b) Source

Generalized version of mapConcurrently.

data Concurrently m a where Source

Generalized version of Concurrently.

A value of type Concurrently m a is an IO-based 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 IO-based lifted 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 :: Forall (Pure m) => m a -> Concurrently m a 

Fields

runConcurrently :: m a