lifted-async-0.10.2.3: Run lifted IO operations asynchronously and wait for their results
CopyrightCopyright (C) 2012-2018 Mitsutoshi Aoe
LicenseBSD-style (see the file LICENSE)
MaintainerMitsutoshi Aoe <maoe@foldr.in>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.Async.Lifted.Safe

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

Instances details
Functor Async 
Instance details

Defined in Control.Concurrent.Async

Methods

fmap :: (a -> b) -> Async a -> Async b #

(<$) :: a -> Async b -> Async a #

Eq (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

(==) :: Async a -> Async a -> Bool #

(/=) :: Async a -> Async a -> Bool #

Ord (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

compare :: Async a -> Async a -> Ordering #

(<) :: Async a -> Async a -> Bool #

(<=) :: Async a -> Async a -> Bool #

(>) :: Async a -> Async a -> Bool #

(>=) :: Async a -> Async a -> Bool #

max :: Async a -> Async a -> Async a #

min :: Async a -> Async a -> Async a #

Hashable (Async a) 
Instance details

Defined in Control.Concurrent.Async

Methods

hashWithSalt :: Int -> Async a -> Int #

hash :: Async a -> Int #

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

Instances details
StM m a ~ a => Pure m a Source # 
Instance details

Defined in Control.Concurrent.Async.Lifted.Safe

type family Forall (p :: k -> Constraint) #

A representation of the quantified constraint forall a. p a.

Instances

Instances details
type Forall (p :: k -> Constraint) 
Instance details

Defined in Data.Constraint.Forall

type Forall (p :: k -> Constraint) = Forall_ p

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. (MonadBase IO m, Forall (Pure m)) => Async a -> m a Source #

Generalized version of wait.

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

Generalized version of poll.

waitCatch :: forall m a. (MonadBase 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.

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

Generalized version of uninterruptibleCancel.

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.

data AsyncCancelled #

The exception thrown by cancel to terminate a thread.

Constructors

AsyncCancelled 

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

Generalized version of waitAny.

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

Generalized version of waitAnyCatch.

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

Generalized version of waitAnyCancel.

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

Generalized version of waitAnyCatchCancel.

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

Generalized version of waitEither.

waitEitherCatch :: forall m a b. (MonadBase 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. (MonadBase IO m, Forall (Pure m)) => Async a -> Async b -> m (Either a b) Source #

Generalized version of waitEitherCancel.

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

Generalized version of waitEitherCatchCancel.

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

Generalized version of waitEither_

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

Generalized version of waitBoth.

Waiting for multiple Asyncs in STM

waitAnySTM :: [Async a] -> STM (Async a, a) #

A version of waitAny that can be used inside an STM transaction.

Since: async-2.1.0

waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a) #

A version of waitAnyCatch that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherSTM :: Async a -> Async b -> STM (Either a b) #

A version of waitEither that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b)) #

A version of waitEitherCatch that can be used inside an STM transaction.

Since: async-2.1.0

waitEitherSTM_ :: Async a -> Async b -> STM () #

A version of waitEither_ that can be used inside an STM transaction.

Since: async-2.1.0

waitBothSTM :: Async a -> Async b -> STM (a, b) #

A version of waitBoth that can be used inside an STM transaction.

Since: async-2.1.0

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.

concurrently_ :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m () 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.

mapConcurrently_ :: (Foldable t, MonadBaseControl IO m, Forall (Pure m)) => (a -> m b) -> t a -> m () Source #

Generalized version of mapConcurrently_.

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

Generalized version of forConcurrently.

forConcurrently_ :: (Foldable t, MonadBaseControl IO m, Forall (Pure m)) => t a -> (a -> m b) -> m () Source #

Generalized version of forConcurrently_.

replicateConcurrently :: (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> m [a] Source #

Generalized version of replicateConcurrently.

replicateConcurrently_ :: (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> m () Source #

Generalized version of replicateConcurrently_.

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 

Fields

Instances

Instances details
Functor m => Functor (Concurrently m) Source # 
Instance details

Defined in Control.Concurrent.Async.Lifted.Safe

Methods

fmap :: (a -> b) -> Concurrently m a -> Concurrently m b #

(<$) :: a -> Concurrently m b -> Concurrently m a #

(MonadBaseControl IO m, Forall (Pure m)) => Applicative (Concurrently m) Source # 
Instance details

Defined in Control.Concurrent.Async.Lifted.Safe

Methods

pure :: a -> Concurrently m a #

(<*>) :: Concurrently m (a -> b) -> Concurrently m a -> Concurrently m b #

liftA2 :: (a -> b -> c) -> Concurrently m a -> Concurrently m b -> Concurrently m c #

(*>) :: Concurrently m a -> Concurrently m b -> Concurrently m b #

(<*) :: Concurrently m a -> Concurrently m b -> Concurrently m a #

(MonadBaseControl IO m, Forall (Pure m)) => Alternative (Concurrently m) Source # 
Instance details

Defined in Control.Concurrent.Async.Lifted.Safe

Methods

empty :: Concurrently m a #

(<|>) :: Concurrently m a -> Concurrently m a -> Concurrently m a #

some :: Concurrently m a -> Concurrently m [a] #

many :: Concurrently m a -> Concurrently m [a] #

(MonadBaseControl IO m, Semigroup a, Forall (Pure m)) => Semigroup (Concurrently m a) Source # 
Instance details

Defined in Control.Concurrent.Async.Lifted.Safe

Methods

(<>) :: Concurrently m a -> Concurrently m a -> Concurrently m a #

sconcat :: NonEmpty (Concurrently m a) -> Concurrently m a #

stimes :: Integral b => b -> Concurrently m a -> Concurrently m a #

(MonadBaseControl IO m, Semigroup a, Monoid a, Forall (Pure m)) => Monoid (Concurrently m a) Source # 
Instance details

Defined in Control.Concurrent.Async.Lifted.Safe

compareAsyncs :: Async a -> Async b -> Ordering #

Compare two Asyncs that may have different types by their ThreadId.