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

Stabilityexperimental
MaintainerMitsutoshi Aoe <maoe@foldr.in>
Safe HaskellNone

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.

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 
Eq (Async a) 
Eq (Async a) => Ord (Async a) 

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 bSource

Generalized version of withAsync.

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

Generalized version of withAsyncBound.

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

Generalized version of withAsyncOn.

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

Generalized version of withAsyncWithUnmask.

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

Generalized version of withAsyncOnWithUnmask.

Quering Asyncs

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

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 (StM m a) -> m ()Source

Generalized version of catch.

cancelWith :: (MonadBase IO m, Exception e) => Async (StM m 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 :: 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 :: MonadBase IO m => [Async a] -> m (Async 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 (StM m a) -> Async (StM m b) -> m ()Source

Generalized version of waitEither_.

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 (StM m a) -> m ()Source

Generalized version of link.

link2 :: MonadBase IO m => Async (StM m a) -> Async (StM m b) -> 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_.

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.

data Concurrently a

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

Calling runConcurrently on a value of type Concurrently a will execute the IO 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")