simple-effects-0.13.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 thread m Source #

Constructors

AsyncMethods 

Fields

Instances
ThreadIdentifier thread => Effect (Async thread) Source # 
Instance details

Defined in Control.Effects.Async

Associated Types

type CanLift (Async thread) t :: Constraint Source #

type ExtraConstraint (Async thread) m :: Constraint Source #

Methods

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

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

MonadEffect (Async AsyncThread) IO Source #

The IO implementation uses the async library.

Instance details

Defined in Control.Effects.Async

UniqueEffect Async IO AsyncThread Source # 
Instance details

Defined in Control.Effects.Async

UniqueEffect Async (RuntimeImplemented (Async thread) m) (thread :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effects.Async

type CanLift (Async thread) t Source # 
Instance details

Defined in Control.Effects.Async

type CanLift (Async thread) t = RunnableTrans t
type ExtraConstraint (Async thread) m Source # 
Instance details

Defined in Control.Effects.Async

type ExtraConstraint (Async thread) m = UniqueEffect Async m thread

class ThreadIdentifier thread where Source #

Methods

mapThread :: (m a -> n b) -> thread m a -> thread n b Source #

Instances
ThreadIdentifier AsyncThread Source # 
Instance details

Defined in Control.Effects.Async

Methods

mapThread :: (m a -> n b) -> AsyncThread m a -> AsyncThread n b Source #

async :: MonadEffect (Async thread) m => m a -> m (thread 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 in the 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 thread) m => thread 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

isAsyncDone :: MonadEffect (Async thread) m => thread n a -> m Bool Source #

Check if the asynchronous computation has finished (either normally, or with an exception)

cancelAsync :: MonadEffect (Async thread) m => thread n a -> m () Source #

Abort the asynchronous exception

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
ThreadIdentifier AsyncThread Source # 
Instance details

Defined in Control.Effects.Async

Methods

mapThread :: (m a -> n b) -> AsyncThread m a -> AsyncThread n b Source #

Functor m => Functor (AsyncThread m) Source # 
Instance details

Defined in Control.Effects.Async

Methods

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

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

MonadEffect (Async AsyncThread) IO Source #

The IO implementation uses the async library.

Instance details

Defined in Control.Effects.Async

Eq (AsyncThread m a) Source # 
Instance details

Defined in Control.Effects.Async

Methods

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

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

Ord (AsyncThread m a) Source # 
Instance details

Defined in Control.Effects.Async

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 #

UniqueEffect Async IO AsyncThread Source # 
Instance details

Defined in Control.Effects.Async

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.

parallelMapM :: (MonadEffect (Async thread) m, Traversable t) => (a -> m b) -> t a -> m (t b) Source #

Like mapM but the supplied function is run in parallel asynchronously on all the elements. The results will be in the same order as the inputs.

parallelMapM_ :: (MonadEffect (Async thread) m, Traversable t) => (a -> m b) -> t a -> m () Source #

Same as parallelMapM_ but discards the result.