monad-schedule-0.2: A new, simple, composable concurrency abstraction.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Schedule.FreeAsync

Description

Asynchronicity implementation using MVars and free monads.

Synopsis

FreeAsyncT

newtype FreeAsyncT m a Source #

An IO-like monad with the capability of async/await-style futures.

Synchronous (blocking) computations in this monad can be created using lift and liftIO. Asynchronous computations that can run in the background are created with freeAsync or asyncMVar.

To leverage the asynchronicity, you can schedule computations with MonadSchedule operations such as schedule or race.

Caution: Composing computations with Applicative or Monad operations like <*>, >>= and do-notation will force all but the final computation in order: When running a *> b *> c, b will not be started before a has completed. To start all operations and run them concurrently, use e.g. scheduleWith. To use an Applicative interface for concurrency, have a look at ConcurrentlyT.

Constructors

FreeAsyncT 

Fields

Instances

Instances details
MonadTrans FreeAsyncT Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

lift :: Monad m => m a -> FreeAsyncT m a #

MonadIO m => MonadIO (FreeAsyncT m) Source #

Lifts into FreeAsyncT without concurrency. See freeAsync.

Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

liftIO :: IO a -> FreeAsyncT m a #

Monad m => Applicative (FreeAsyncT m) Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

pure :: a -> FreeAsyncT m a #

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

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

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

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

Monad m => Functor (FreeAsyncT m) Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

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

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

Monad m => Monad (FreeAsyncT m) Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

(>>=) :: FreeAsyncT m a -> (a -> FreeAsyncT m b) -> FreeAsyncT m b #

(>>) :: FreeAsyncT m a -> FreeAsyncT m b -> FreeAsyncT m b #

return :: a -> FreeAsyncT m a #

MonadIO m => MonadSchedule (FreeAsyncT m) Source #

Concurrently wait for the completion of IO actions. Has a slight runtime overhead over the direct MonadSchedule IO instance, but better fairness.

Instance details

Defined in Control.Monad.Schedule.FreeAsync

freeAsync :: MonadIO m => IO a -> FreeAsyncT m a Source #

Run an IO computation in the background.

This returns a "promise", or "future", which completes the computation when run.

asyncMVar :: MVar a -> FreeAsyncT m a Source #

Asynchronously await an MVar.

asyncMVar var will attempt takeMVar in a way that can be scheduled concurrently with other asyncMVars or freeAsyncs.

runFreeAsync :: FreeAsync a -> IO a Source #

Like runFreeAsyncT, but specialized to IO.

runFreeAsyncT :: MonadIO m => FreeAsyncT m a -> m a Source #

Complete all computations and remove the FreeAsyncT layer.

Concurrent Applicative interface

newtype ConcurrentlyT m a Source #

Like FreeAsyncT, but leverages concurrency in the Applicative interface.

The central difference to FreeAsyncT is the Applicative instance: concurrently a *> concurrently b *> concurrently c will launch all three actions immediately and return when all actions have completed. On the other hand, concurrently a >>= f has to compute sequentially.

For more readable syntax, it can be useful to switch the ApplicativeDo extension on.

The downside of this Applicative instance is that ConcurrentlyT can't be an instance of MonadTrans. As a drop-in replacement, the function lift' is supplied.

Caution: To lift an IO action concurrently, you need to use concurrently and not liftIO.

Constructors

ConcurrentlyT 

Instances

Instances details
MonadIO m => MonadIO (ConcurrentlyT m) Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

liftIO :: IO a -> ConcurrentlyT m a #

MonadIO m => Applicative (ConcurrentlyT m) Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

pure :: a -> ConcurrentlyT m a #

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

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

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

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

Monad m => Functor (ConcurrentlyT m) Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

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

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

MonadIO m => Monad (ConcurrentlyT m) Source # 
Instance details

Defined in Control.Monad.Schedule.FreeAsync

Methods

(>>=) :: ConcurrentlyT m a -> (a -> ConcurrentlyT m b) -> ConcurrentlyT m b #

(>>) :: ConcurrentlyT m a -> ConcurrentlyT m b -> ConcurrentlyT m b #

return :: a -> ConcurrentlyT m a #

MonadIO m => MonadSchedule (ConcurrentlyT m) Source #

Like FreeAsyncT, but executes actions composed via the Applicative interface concurrently.

Instance details

Defined in Control.Monad.Schedule.FreeAsync

concurrently :: MonadIO m => IO a -> ConcurrentlyT m a Source #

Lift an IO action such that it can be run concurrently.

See freeAsync.

lift' :: Monad m => m a -> ConcurrentlyT m a Source #

Lift a computation to ConcurrentlyT.

This replaces the missing MonadTrans instance.

Caution: Computations lifted with this function cannot be scheduled concurrently! If this is your intention, concurrently needs to be used instead.

runConcurrentlyT :: MonadIO m => ConcurrentlyT m a -> m a Source #

Run a ConcurrentlyT computation to completion, removing the newtype layers.

runConcurrently :: Concurrently a -> IO a Source #

Like runConcurrently, but specialised to IO.