extensible-effects-concurrent-0.1.2.2: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.MessagePassing

Description

The message passing effect.

This module describes an abstract message passing effect, and a process effect, mimicking Erlang's process and message semantics.

An implementation of a handler for these effects can be found in Dispatcher.

Synopsis

Documentation

newtype ProcessId Source #

Each process is identified by a single process id, that stays constant throughout the life cycle of a process. Also, message sending relies on these values to address messages to processes.

Constructors

ProcessId 

Fields

Instances

Bounded ProcessId Source # 
Enum ProcessId Source # 
Eq ProcessId Source # 
Integral ProcessId Source # 
Num ProcessId Source # 
Ord ProcessId Source # 
Read ProcessId Source # 
Real ProcessId Source # 
Show ProcessId Source # 

data Process b where Source #

The process effect is the basis for message passing concurrency. This binds the semantics of a process with a process-id, and some process flags, and the ability to leave a process early with an error.

Instances

MonadLog String (Eff ProcIO) # 

Methods

logMessageFree :: (forall n. Monoid n => (String -> n) -> n) -> Eff ProcIO () #

self :: Member Process r => Eff r ProcessId Source #

Returns the ProcessId of the current process.

trapExit :: Member Process r => Bool -> Eff r () Source #

Set the flag that controls a process reaction to exit messages from linked/monitored processes.

getTrapExit :: Member Process r => Eff r Bool Source #

Return the trapExit flag.

raiseError :: Member Process r => String -> Eff r b Source #

Thrown an error, can be caught by catchProcessError.

catchProcessError :: forall r w. Member Process r => (String -> Eff r w) -> Eff r w -> Eff r w Source #

Catch and handle an error raised by raiseError. Works independent of the handler implementation.

ignoreProcessError :: (HasCallStack, Member Process r) => Eff r a -> Eff r (Either String a) Source #

Like catchProcessError it catches raiseError, but instead of invoking a user provided handler, the result is wrapped into an Either.

data MessagePassing b where Source #

An effect for sending and receiving messages.

Constructors

SendMessage :: Typeable m => ProcessId -> m -> MessagePassing Bool

Send a message to a process addressed by the ProcessId. Sending a message should **always succeed** and return **immediately**, even if the destination process does not exist, or does not accept messages of the given type.

ReceiveMessage :: forall e m. (Typeable m, Typeable (Message m)) => (m -> e) -> MessagePassing (Message e)

Receive a message. This should block until an a message was received. The pure function may convert the incoming message into something, and the result is returned as Message value. Another reason why this function returns, is if a process control message was sent to the process. This can only occur from inside the runtime system, aka the effect handler implementation. (Currently there is one in Dispatcher.)

Instances

MonadLog String (Eff ProcIO) # 

Methods

logMessageFree :: (forall n. Monoid n => (String -> n) -> n) -> Eff ProcIO () #

data Message m where Source #

When a process invokes receiveMessage a value of this type is returned. There are more reasons that receiveMessage might return, one is that a message was sent to the process, another might be that in internal, handler specific, event occurred for which the process should wake-up.

Constructors

ProcessControlMessage :: String -> Message m 
Message :: m -> Message m 

Instances

Functor Message Source # 

Methods

fmap :: (a -> b) -> Message a -> Message b #

(<$) :: a -> Message b -> Message a #

Foldable Message Source # 

Methods

fold :: Monoid m => Message m -> m #

foldMap :: Monoid m => (a -> m) -> Message a -> m #

foldr :: (a -> b -> b) -> b -> Message a -> b #

foldr' :: (a -> b -> b) -> b -> Message a -> b #

foldl :: (b -> a -> b) -> b -> Message a -> b #

foldl' :: (b -> a -> b) -> b -> Message a -> b #

foldr1 :: (a -> a -> a) -> Message a -> a #

foldl1 :: (a -> a -> a) -> Message a -> a #

toList :: Message a -> [a] #

null :: Message a -> Bool #

length :: Message a -> Int #

elem :: Eq a => a -> Message a -> Bool #

maximum :: Ord a => Message a -> a #

minimum :: Ord a => Message a -> a #

sum :: Num a => Message a -> a #

product :: Num a => Message a -> a #

Traversable Message Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Message a -> f (Message b) #

sequenceA :: Applicative f => Message (f a) -> f (Message a) #

mapM :: Monad m => (a -> m b) -> Message a -> m (Message b) #

sequence :: Monad m => Message (m a) -> m (Message a) #

Eq m => Eq (Message m) Source # 

Methods

(==) :: Message m -> Message m -> Bool #

(/=) :: Message m -> Message m -> Bool #

Ord m => Ord (Message m) Source # 

Methods

compare :: Message m -> Message m -> Ordering #

(<) :: Message m -> Message m -> Bool #

(<=) :: Message m -> Message m -> Bool #

(>) :: Message m -> Message m -> Bool #

(>=) :: Message m -> Message m -> Bool #

max :: Message m -> Message m -> Message m #

min :: Message m -> Message m -> Message m #

Show m => Show (Message m) Source # 

Methods

showsPrec :: Int -> Message m -> ShowS #

show :: Message m -> String #

showList :: [Message m] -> ShowS #

sendMessage :: forall o r. (HasCallStack, Member MessagePassing r, Typeable o) => ProcessId -> o -> Eff r Bool Source #

Send a message to a process addressed by the ProcessId. @see SendMessage.

receiveMessage :: forall o r. (HasCallStack, Member MessagePassing r, Member Process r, Typeable o) => Proxy o -> Eff r (Message o) Source #

Block until a message was received. Expect a message of the type annotated by the Proxy. Depending on trapExit, this will raiseError. @see ReceiveMessage.