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

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

Control.Concurrent.Async.Lifted

Contents

Description

This is a wrapped version of Control.Concurrent.Async with types generalized from IO to all monads in either MonadBase or MonadBaseControl.

All the functions restore the monadic effects in the forked computation unless specified otherwise.

If your monad stack satisfies StM m a ~ a (e.g. the reader monad), consider using Control.Concurrent.Async.Lifted.Safe module, which prevents you from messing up monadic effects.

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

Spawning

async :: MonadBaseControl IO m => m a -> m (Async (StM m a)) Source

Generalized version of async.

asyncBound :: MonadBaseControl IO m => m a -> m (Async (StM m a)) Source

Generalized version of asyncBound.

asyncOn :: MonadBaseControl IO m => Int -> m a -> m (Async (StM m a)) Source

Generalized version of asyncOn.

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

Generalized version of asyncWithUnmask.

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

Generalized version of asyncOnWithUnmask.

Spawning with automatic cancelation

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

Generalized version of withAsync.

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

Generalized version of withAsyncBound.

withAsyncOn :: MonadBaseControl IO m => Int -> m a -> (Async (StM m a) -> m b) -> m b Source

Generalized version of withAsyncOn.

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

Generalized version of withAsyncWithUnmask.

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

Generalized version of withAsyncOnWithUnmask.

Quering Asyncs

wait :: MonadBaseControl IO m => Async (StM m a) -> m a Source

Generalized version of wait.

poll :: MonadBaseControl IO m => Async (StM m a) -> m (Maybe (Either SomeException a)) Source

Generalized version of poll.

waitCatch :: MonadBaseControl IO m => Async (StM m a) -> m (Either SomeException a) Source

Generalized version of waitCatch.

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

Generalized version of cancel.

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

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

Generalized version of cancelWith.

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

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

Generalized version of waitAny.

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

Generalized version of waitAnyCatch.

waitAnyCancel :: MonadBaseControl IO m => [Async (StM m a)] -> m (Async (StM m a), a) Source

Generalized version of waitAnyCancel.

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

Generalized version of waitAnyCatchCancel.

waitEither :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either a b) Source

Generalized version of waitEither.

waitEitherCancel :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m b) -> m (Either a b) Source

Generalized version of waitEitherCancel.

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 :: MonadBaseControl IO m => Async (StM m a) -> Async (StM m 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 a -> m () Source

Generalized version of link2.

Convenient utilities

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

Generalized version of race.

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

Generalized version of race_.

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

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

Generalized version of concurrently.

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

Generalized version of mapConcurrently.

newtype Concurrently m a 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 

Fields

runConcurrently :: m a