Copyright | Copyright (C) 2012-2018 Mitsutoshi Aoe |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Mitsutoshi Aoe <maoe@foldr.in> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This is a safe variant of Control.Concurrent.Async.Lifted
.
This module assumes your monad stack to satisfy
so you can't
mess up monadic effects. If your monad stack is stateful, use
StM
m a ~ aControl.Concurrent.Async.Lifted
with special care.
Synopsis
- data Async a
- class StM m a ~ a => Pure m a
- type family Forall (p :: k -> Constraint) :: Constraint
- async :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m (Async a)
- asyncBound :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m (Async a)
- asyncOn :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> m (Async a)
- asyncWithUnmask :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => ((forall b. m b -> m b) -> m a) -> m (Async a)
- asyncOnWithUnmask :: forall m a. (MonadBaseControl IO m, Forall (Pure m)) => Int -> ((forall b. m b -> m b) -> m a) -> m (Async a)
- withAsync :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> (Async a -> m b) -> m b
- withAsyncBound :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> (Async a -> m b) -> m b
- withAsyncOn :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> (Async a -> m b) -> m b
- 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
- 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
- wait :: forall m a. (MonadBase IO m, Forall (Pure m)) => Async a -> m a
- poll :: forall m a. (MonadBase IO m, Forall (Pure m)) => Async a -> m (Maybe (Either SomeException a))
- waitCatch :: forall m a. (MonadBase IO m, Forall (Pure m)) => Async a -> m (Either SomeException a)
- cancel :: MonadBase IO m => Async a -> m ()
- uninterruptibleCancel :: MonadBase IO m => Async a -> m ()
- cancelWith :: (MonadBase IO m, Exception e) => Async a -> e -> m ()
- asyncThreadId :: Async a -> ThreadId
- data AsyncCancelled = AsyncCancelled
- waitSTM :: Async a -> STM a
- pollSTM :: Async a -> STM (Maybe (Either SomeException a))
- waitCatchSTM :: Async a -> STM (Either SomeException a)
- waitAny :: forall m a. (MonadBase IO m, Forall (Pure m)) => [Async a] -> m (Async a, a)
- waitAnyCatch :: forall m a. (MonadBase IO m, Forall (Pure m)) => [Async a] -> m (Async a, Either SomeException a)
- waitAnyCancel :: forall m a. (MonadBase IO m, Forall (Pure m)) => [Async a] -> m (Async a, a)
- waitAnyCatchCancel :: forall m a. (MonadBase IO m, Forall (Pure m)) => [Async a] -> m (Async a, Either SomeException a)
- waitEither :: forall m a b. (MonadBase IO m, Forall (Pure m)) => Async a -> Async b -> m (Either a b)
- waitEitherCatch :: forall m a b. (MonadBase IO m, Forall (Pure m)) => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEitherCancel :: forall m a b. (MonadBase IO m, Forall (Pure m)) => Async a -> Async b -> m (Either a b)
- waitEitherCatchCancel :: forall m a b. (MonadBase IO m, Forall (Pure m)) => Async a -> Async b -> m (Either (Either SomeException a) (Either SomeException b))
- waitEither_ :: MonadBase IO m => Async a -> Async b -> m ()
- waitBoth :: forall m a b. (MonadBase IO m, Forall (Pure m)) => Async a -> Async b -> m (a, b)
- waitAnySTM :: [Async a] -> STM (Async a, a)
- waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a)
- waitEitherSTM :: Async a -> Async b -> STM (Either a b)
- waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b))
- waitEitherSTM_ :: Async a -> Async b -> STM ()
- waitBothSTM :: Async a -> Async b -> STM (a, b)
- link :: MonadBase IO m => Async a -> m ()
- link2 :: MonadBase IO m => Async a -> Async b -> m ()
- data ExceptionInLinkedThread where
- ExceptionInLinkedThread :: forall a. Async a -> SomeException -> ExceptionInLinkedThread
- race :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m (Either a b)
- race_ :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m ()
- concurrently :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m (a, b)
- concurrently_ :: forall m a b. (MonadBaseControl IO m, Forall (Pure m)) => m a -> m b -> m ()
- mapConcurrently :: (Traversable t, MonadBaseControl IO m, Forall (Pure m)) => (a -> m b) -> t a -> m (t b)
- mapConcurrently_ :: (Foldable t, MonadBaseControl IO m, Forall (Pure m)) => (a -> m b) -> t a -> m ()
- forConcurrently :: (Traversable t, MonadBaseControl IO m, Forall (Pure m)) => t a -> (a -> m b) -> m (t b)
- forConcurrently_ :: (Foldable t, MonadBaseControl IO m, Forall (Pure m)) => t a -> (a -> m b) -> m ()
- replicateConcurrently :: (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> m [a]
- replicateConcurrently_ :: (MonadBaseControl IO m, Forall (Pure m)) => Int -> m a -> m ()
- data Concurrently m a where
- Concurrently :: Forall (Pure m) => {..} -> Concurrently m a
- compareAsyncs :: Async a -> Async b -> Ordering
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
).
class StM m a ~ a => Pure m a Source #
Most of the functions in this module have
in their
constraints, which means they require the monad Forall
(Pure
m)m
satisfies
for all StM
m a ~ aa
.
Instances
StM m a ~ a => Pure m a Source # | |
Defined in Control.Concurrent.Async.Lifted.Safe |
type family Forall (p :: k -> Constraint) :: Constraint #
A representation of the quantified constraint forall a. p a
.
Instances
type Forall (p :: k -> Constraint) | |
Defined in Data.Constraint.Forall |
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 cancel
ation
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 Async
s
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
.
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
.
data AsyncCancelled #
The exception thrown by cancel
to terminate a thread.
Instances
Eq AsyncCancelled | |
Defined in Control.Concurrent.Async (==) :: AsyncCancelled -> AsyncCancelled -> Bool # (/=) :: AsyncCancelled -> AsyncCancelled -> Bool # | |
Show AsyncCancelled | |
Defined in Control.Concurrent.Async showsPrec :: Int -> AsyncCancelled -> ShowS # show :: AsyncCancelled -> String # showList :: [AsyncCancelled] -> ShowS # | |
Exception AsyncCancelled | |
Defined in Control.Concurrent.Async |
STM operations
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 Async
s
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 Async
s 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
data ExceptionInLinkedThread where #
ExceptionInLinkedThread :: forall a. Async a -> SomeException -> ExceptionInLinkedThread |
Instances
Show ExceptionInLinkedThread | |
Defined in Control.Concurrent.Async showsPrec :: Int -> ExceptionInLinkedThread -> ShowS # show :: ExceptionInLinkedThread -> String # showList :: [ExceptionInLinkedThread] -> ShowS # | |
Exception ExceptionInLinkedThread | |
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
is an IO-based operation that can be
composed with other Concurrently
m aConcurrently
values, using the Applicative
and
Alternative
instances.
Calling runConcurrently
on a value of type
will
execute the IO-based lifted operations it contains concurrently, before
delivering the result of type Concurrently
m aa
.
For example
(page1, page2, page3) <-runConcurrently
$ (,,)<$>
Concurrently
(getURL "url1")<*>
Concurrently
(getURL "url2")<*>
Concurrently
(getURL "url3")
Concurrently | |
|
Instances
compareAsyncs :: Async a -> Async b -> Ordering #
Compare two Asyncs that may have different types by their ThreadId.