simple-effects-0.12.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Async

Description

The Async effect allows you to fork new threads in monads other than just IO.

Synopsis

Documentation

data Async m Source #

Constructors

AsyncMethods 

Fields

Instances

Effect Async Source # 

Associated Types

type CanLift (Async :: (* -> *) -> *) (t :: (* -> *) -> * -> *) :: Constraint Source #

Methods

liftThrough :: (CanLift Async t, Monad m, Monad (t m)) => Async m -> Async (t m) Source #

mergeContext :: Monad m => m (Async m) -> Async m Source #

MonadEffect Async IO Source #

The IO implementation uses the async library.

Methods

effect :: Async IO Source #

type CanLift Async t Source # 

newtype AsyncThread m a Source #

The type that represents the forked computation in the monad m that eventually computes a value of type a. Depending on the monad, the computation may produce zero, one or even multiple values of that type.

Constructors

AsyncThread (Async (m a)) 

Instances

Functor m => Functor (AsyncThread m) Source # 

Methods

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

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

Eq (AsyncThread m a) Source # 

Methods

(==) :: AsyncThread m a -> AsyncThread m a -> Bool #

(/=) :: AsyncThread m a -> AsyncThread m a -> Bool #

Ord (AsyncThread m a) Source # 

Methods

compare :: AsyncThread m a -> AsyncThread m a -> Ordering #

(<) :: AsyncThread m a -> AsyncThread m a -> Bool #

(<=) :: AsyncThread m a -> AsyncThread m a -> Bool #

(>) :: AsyncThread m a -> AsyncThread m a -> Bool #

(>=) :: AsyncThread m a -> AsyncThread m a -> Bool #

max :: AsyncThread m a -> AsyncThread m a -> AsyncThread m a #

min :: AsyncThread m a -> AsyncThread m a -> AsyncThread m a #

async :: MonadEffect Async m => m a -> m (AsyncThread m a) Source #

Fork a new thread to run the given computation. The monadic context is forked into the new thread.

For example, if we use state, the current state value will be visible int he forked computation. Depending on how we ultimately implement the state, modifying it may or may not be visible from the main thread. If we use implementStateViaStateT then setting the state in the forked thread will just modify the thread-local value. On the other hand, if we use implementStateViaIORef then both the main thread and the new thread will use the same reference meaning they can interact through it.

waitAsync :: MonadEffect Async m => AsyncThread m a -> m a Source #

Wait for the thread to finish and return it's result. The monadic context will also be merged.

Example:

 setState @Int 1
 th <- async $ do
     setState @Int 2
 waitAsync th
 print =<< getState @Int -- Outputs 2

implementAsyncViaIO :: IO a -> IO a Source #

This will discard the MonadEffect Async m constraint by forcing m to be IO. The functions doesn't actually do anything, the real implementation is given by the MonadEffect Async IO instance which uses the async package.