-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Run IO operations asynchronously and wait for their results -- -- This package provides a higher-level interface over threads, in which -- an Async a is a concurrent thread that will eventually -- deliver a value of type a. The package provides ways to -- create Async computations, wait for their results, and cancel -- them. -- -- Using Async is safer than using threads in two ways: -- -- @package async @version 2.1.1.1 -- | This module provides a set of operations for running IO operations -- asynchronously and waiting for their results. It is a thin layer over -- the basic concurrency operations provided by -- Control.Concurrent. The main additional functionality it -- provides is the ability to wait for the return value of a thread, but -- the interface also provides some additional safety and robustness over -- using threads and MVar directly. -- -- The basic type is Async a, which represents an -- asynchronous IO action that will return a value of type -- a, or die with an exception. An Async corresponds to -- a thread, and its ThreadId can be obtained with -- asyncThreadId, although that should rarely be necessary. -- -- For example, to fetch two web pages at the same time, we could do this -- (assuming a suitable getURL function): -- --
--   do a1 <- async (getURL url1)
--      a2 <- async (getURL url2)
--      page1 <- wait a1
--      page2 <- wait a2
--      ...
--   
-- -- where async starts the operation in a separate thread, and -- wait waits for and returns the result. If the operation throws -- an exception, then that exception is re-thrown by wait. This is -- one of the ways in which this library provides some additional safety: -- it is harder to accidentally forget about exceptions thrown in child -- threads. -- -- A slight improvement over the previous example is this: -- --
--   withAsync (getURL url1) $ \a1 -> do
--   withAsync (getURL url2) $ \a2 -> do
--   page1 <- wait a1
--   page2 <- wait a2
--   ...
--   
-- -- withAsync is like async, except that the Async is -- automatically killed (using uninterruptibleCancel) if the -- enclosing IO operation returns before it has completed. Consider the -- case when the first wait throws an exception; then the second -- Async will be automatically killed rather than being left to -- run in the background, possibly indefinitely. This is the second way -- that the library provides additional safety: using withAsync -- means we can avoid accidentally leaving threads running. Furthermore, -- withAsync allows a tree of threads to be built, such that -- children are automatically killed if their parents die for any reason. -- -- The pattern of performing two IO actions concurrently and waiting for -- their results is packaged up in a combinator concurrently, so -- we can further shorten the above example to: -- --
--   (page1, page2) <- concurrently (getURL url1) (getURL url2)
--   ...
--   
-- -- The Functor instance can be used to change the result of an -- Async. For example: -- --
--   ghci> a <- async (return 3)
--   ghci> wait a
--   3
--   ghci> wait (fmap (+1) a)
--   4
--   
module Control.Concurrent.Async -- | 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). data Async a -- | Spawn an asynchronous action in a separate thread. async :: IO a -> IO (Async a) -- | Like async but using forkOS internally. asyncBound :: IO a -> IO (Async a) -- | Like async but using forkOn internally. asyncOn :: Int -> IO a -> IO (Async a) -- | Like async but using forkIOWithUnmask internally. The -- child thread is passed a function that can be used to unmask -- asynchronous exceptions. asyncWithUnmask :: ((forall b. IO b -> IO b) -> IO a) -> IO (Async a) -- | Like asyncOn but using forkOnWithUnmask internally. The -- child thread is passed a function that can be used to unmask -- asynchronous exceptions. asyncOnWithUnmask :: Int -> ((forall b. IO b -> IO b) -> IO a) -> IO (Async a) -- | Spawn an asynchronous action in a separate thread, and pass its -- Async handle to the supplied function. When the function -- returns or throws an exception, uninterruptibleCancel is called -- on the Async. -- --
--   withAsync action inner = bracket (async action) uninterruptibleCancel inner
--   
-- -- This is a useful variant of async that ensures an -- Async is never left running unintentionally. withAsync :: IO a -> (Async a -> IO b) -> IO b -- | Like withAsync but uses forkOS internally. withAsyncBound :: IO a -> (Async a -> IO b) -> IO b -- | Like withAsync but uses forkOn internally. withAsyncOn :: Int -> IO a -> (Async a -> IO b) -> IO b -- | Like withAsync but uses forkIOWithUnmask internally. The -- child thread is passed a function that can be used to unmask -- asynchronous exceptions. withAsyncWithUnmask :: ((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b -- | Like withAsyncOn but uses forkOnWithUnmask internally. -- The child thread is passed a function that can be used to unmask -- asynchronous exceptions withAsyncOnWithUnmask :: Int -> ((forall c. IO c -> IO c) -> IO a) -> (Async a -> IO b) -> IO b -- | Wait for an asynchronous action to complete, and return its value. If -- the asynchronous action threw an exception, then the exception is -- re-thrown by wait. -- --
--   wait = atomically . waitSTM
--   
wait :: Async a -> IO a -- | Check whether an Async has completed yet. If it has not -- completed yet, then the result is Nothing, otherwise the -- result is Just e where e is Left x if the -- Async raised an exception x, or Right a if -- it returned a value a. -- --
--   poll = atomically . pollSTM
--   
poll :: Async a -> IO (Maybe (Either SomeException a)) -- | Wait for an asynchronous action to complete, and return either -- Left e if the action raised an exception e, or -- Right a if it returned a value a. -- --
--   waitCatch = atomically . waitCatchSTM
--   
waitCatch :: Async a -> IO (Either SomeException a) -- | Cancel an asynchronous action by throwing the ThreadKilled -- exception to it, and waiting for the Async thread to quit. Has -- no effect if the Async has already completed. -- --
--   cancel a = throwTo (asyncThreadId a) ThreadKilled <* waitCatch a
--   
-- -- Note that cancel will not terminate until the thread the -- Async refers to has terminated. This means that cancel -- will block for as long said thread blocks when receiving an -- asynchronous exception. -- -- For example, it could block if: -- -- cancel :: Async a -> IO () -- | Cancel an asynchronous action -- -- This is a variant of cancel, but it is not interruptible. uninterruptibleCancel :: Async a -> IO () -- | Cancel an asynchronous action by throwing the supplied exception to -- it. -- --
--   cancelWith a x = throwTo (asyncThreadId a) x
--   
-- -- The notes about the synchronous nature of cancel also apply to -- cancelWith. cancelWith :: Exception e => Async a -> e -> IO () -- | Returns the ThreadId of the thread running the given -- Async. asyncThreadId :: Async a -> ThreadId -- | A version of wait that can be used inside an STM transaction. waitSTM :: Async a -> STM a -- | A version of poll that can be used inside an STM transaction. pollSTM :: Async a -> STM (Maybe (Either SomeException a)) -- | A version of waitCatch that can be used inside an STM -- transaction. waitCatchSTM :: Async a -> STM (Either SomeException a) -- | Wait for any of the supplied Asyncs to complete. If the first -- to complete throws an exception, then that exception is re-thrown by -- waitAny. -- -- If multiple Asyncs complete or have completed, then the value -- returned corresponds to the first completed Async in the list. waitAny :: [Async a] -> IO (Async a, a) -- | Wait for any of the supplied asynchronous operations to complete. The -- value returned is a pair of the Async that completed, and the -- result that would be returned by wait on that Async. -- -- If multiple Asyncs complete or have completed, then the value -- returned corresponds to the first completed Async in the list. waitAnyCatch :: [Async a] -> IO (Async a, Either SomeException a) -- | Like waitAny, but also cancels the other asynchronous -- operations as soon as one has completed. waitAnyCancel :: [Async a] -> IO (Async a, a) -- | Like waitAnyCatch, but also cancels the other asynchronous -- operations as soon as one has completed. waitAnyCatchCancel :: [Async a] -> IO (Async a, Either SomeException a) -- | Wait for the first of two Asyncs to finish. If the -- Async that finished first raised an exception, then the -- exception is re-thrown by waitEither. waitEither :: Async a -> Async b -> IO (Either a b) -- | Wait for the first of two Asyncs to finish. waitEitherCatch :: Async a -> Async b -> IO (Either (Either SomeException a) (Either SomeException b)) -- | Like waitEither, but also cancels both Asyncs -- before returning. waitEitherCancel :: Async a -> Async b -> IO (Either a b) -- | Like waitEitherCatch, but also cancels both -- Asyncs before returning. waitEitherCatchCancel :: Async a -> Async b -> IO (Either (Either SomeException a) (Either SomeException b)) -- | Like waitEither, but the result is ignored. waitEither_ :: Async a -> Async b -> IO () -- | Waits for both Asyncs to finish, but if either of them throws -- an exception before they have both finished, then the exception is -- re-thrown by waitBoth. waitBoth :: Async a -> Async b -> IO (a, b) -- | A version of waitAny that can be used inside an STM -- transaction. waitAnySTM :: [Async a] -> STM (Async a, a) -- | A version of waitAnyCatch that can be used inside an STM -- transaction. waitAnyCatchSTM :: [Async a] -> STM (Async a, Either SomeException a) -- | A version of waitEither that can be used inside an STM -- transaction. waitEitherSTM :: Async a -> Async b -> STM (Either a b) -- | A version of waitEitherCatch that can be used inside an STM -- transaction. waitEitherCatchSTM :: Async a -> Async b -> STM (Either (Either SomeException a) (Either SomeException b)) -- | A version of waitEither_ that can be used inside an STM -- transaction. waitEitherSTM_ :: Async a -> Async b -> STM () -- | A version of waitBoth that can be used inside an STM -- transaction. waitBothSTM :: Async a -> Async b -> STM (a, b) -- | Link the given Async to the current thread, such that if the -- Async raises an exception, that exception will be re-thrown -- in the current thread. link :: Async a -> IO () -- | Link two Asyncs together, such that if either raises an -- exception, the same exception is re-thrown in the other -- Async. link2 :: Async a -> Async b -> IO () -- | Run two IO actions concurrently, and return the first to -- finish. The loser of the race is cancelled. -- --
--   race left right =
--     withAsync left $ \a ->
--     withAsync right $ \b ->
--     waitEither a b
--   
race :: IO a -> IO b -> IO (Either a b) -- | Like race, but the result is ignored. race_ :: IO a -> IO b -> IO () -- | Run two IO actions concurrently, and return both results. If -- either action throws an exception at any time, then the other action -- is cancelled, and the exception is re-thrown by -- concurrently. -- --
--   concurrently left right =
--     withAsync left $ \a ->
--     withAsync right $ \b ->
--     waitBoth a b
--   
concurrently :: IO a -> IO b -> IO (a, b) -- | concurrently, but ignore the result values concurrently_ :: IO a -> IO b -> IO () -- | maps an IO-performing function over any Traversable -- data type, performing all the IO actions concurrently, and -- returning the original data structure with the arguments replaced by -- the results. -- -- For example, mapConcurrently works with lists: -- --
--   pages <- mapConcurrently getURL ["url1", "url2", "url3"]
--   
mapConcurrently :: Traversable t => (a -> IO b) -> t a -> IO (t b) -- | forConcurrently is mapConcurrently with its arguments -- flipped -- --
--   pages <- forConcurrently ["url1", "url2", "url3"] $ \url -> getURL url
--   
forConcurrently :: Traversable t => t a -> (a -> IO b) -> IO (t b) -- | mapConcurrently_ is mapConcurrently with the return -- value discarded, just like @mapM_ mapConcurrently_ :: Foldable f => (a -> IO b) -> f a -> IO () -- | forConcurrently_ is forConcurrently with the return -- value discarded, just like @forM_ forConcurrently_ :: Foldable f => f a -> (a -> IO b) -> IO () -- | Perform the action in the given number of threads. replicateConcurrently :: Int -> IO a -> IO [a] -- | Same as replicateConcurrently, but ignore the results. replicateConcurrently_ :: Int -> IO a -> IO () -- | 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")
--   
newtype Concurrently a Concurrently :: IO a -> Concurrently a [runConcurrently] :: Concurrently a -> IO a instance GHC.Classes.Eq (Control.Concurrent.Async.Async a) instance GHC.Classes.Ord (Control.Concurrent.Async.Async a) instance GHC.Base.Functor Control.Concurrent.Async.Async instance GHC.Base.Functor Control.Concurrent.Async.Concurrently instance GHC.Base.Applicative Control.Concurrent.Async.Concurrently instance GHC.Base.Alternative Control.Concurrent.Async.Concurrently instance Data.Semigroup.Semigroup a => Data.Semigroup.Semigroup (Control.Concurrent.Async.Concurrently a) instance (Data.Semigroup.Semigroup a, GHC.Base.Monoid a) => GHC.Base.Monoid (Control.Concurrent.Async.Concurrently a)