om-fork-0.7.1.7: Concurrency utilities.
Safe HaskellSafe-Inferred
LanguageHaskell2010

OM.Fork

Description

 
Synopsis

Actor Communication.

class Actor a where Source #

The class of types that can act as the handle for an asynchronous actor.

Associated Types

type Msg a Source #

The type of messages associated with the actor.

Methods

actorChan :: a -> Msg a -> IO () Source #

The channel through which messages can be sent to the actor.

Instances

Instances details
Actor (Chan m) Source # 
Instance details

Defined in OM.Fork

Associated Types

type Msg (Chan m) Source #

Methods

actorChan :: Chan m -> Msg (Chan m) -> IO () Source #

data Responder a Source #

How to respond to a asynchronous message.

Instances

Instances details
ToJSON (Responder a) Source # 
Instance details

Defined in OM.Fork

Show (Responder a) Source # 
Instance details

Defined in OM.Fork

data Responded Source #

Proof that respond was called. Clients can use this type in their type signatures when they require that respond be called at least once, because calling respond is the only way to generate values of this type.

respond :: MonadIO m => Responder a -> a -> m Responded Source #

Respond to an asynchronous message.

call Source #

Arguments

:: (Actor actor, MonadIO m) 
=> actor

The actor to which we are sending a call request.

-> (Responder a -> Msg actor)

Given a way for the actor to respond to the message, construct a message that should be sent to the actor.

Typically, your Msg type will look something like this:

data MyMsg
  = MsgWithResponse SomeData (Responder ResponseType)
    -- In this example, this type of message requires a
    -- response. We package the responder up as part of the
    -- message itself. Idiomatically it is best to put the
    -- responder as the last argument so that it is easy to pass
    -- 'MsgWithResponse someData' to 'call'.
  | MsgWithoutResponse SomeData
    -- In this example, this type of message requires no response. It
    -- is a "fire and forget" message.

you will call call like this:

do
  response <- call actor (MsgWithResponse someData)
  -- response :: ResponseType
-> m a 

Send a message to an actor, and wait for a response.

cast :: (Actor actor, MonadIO m) => actor -> Msg actor -> m () Source #

Send a message to an actor, but do not wait for a response.

Forking Background Processes.

logUnexpectedTermination :: (MonadLogger m, MonadCatch m) => ProcessName -> m a -> m a Source #

Log (at WARN) when the action terminates for any reason.

newtype ProcessName Source #

The name of a process.

Constructors

ProcessName 

Fields

Instances

Instances details
IsString ProcessName Source # 
Instance details

Defined in OM.Fork

Monoid ProcessName Source # 
Instance details

Defined in OM.Fork

Semigroup ProcessName Source # 
Instance details

Defined in OM.Fork

Show ProcessName Source # 
Instance details

Defined in OM.Fork

type Race = ?scope :: Scope Source #

This constraint indicates that we are in the context of a thread race. If any threads in the race terminate, then all threads in the race terminate. Threads are "in the race" if they were forked using race.

runRace Source #

Arguments

:: MonadUnliftIO m 
=> (Race => m a)
  • action: The provided "race" action.
-> m a 

Run a thread race.

Within the provided action, you can call race to fork new background threads. When the action terminates, all background threads forked with race are also terminated. Likewise, if any one of the racing threads terminates, then all other racing threads are terminated _and_ runRace will throw an exception.

In any event, when runRace returns, all background threads forked by the action using race will have been terminated.

race :: (MonadCatch m, MonadLogger m, MonadUnliftIO m, Race) => ProcessName -> m a -> m () Source #

Fork a new thread within the context of a race. This thread will be terminated when any other racing thread terminates, or else if this thread terminates first it will cause all other racing threads to be terminated.

Generally, we normally expect that the thread is a "background thread" and will never terminate under "normal" conditions.

wait :: (MonadIO m, Race) => m () Source #

Wait for all racing threads to terminate.