distributed-process-extras-0.3.2: Cloud Haskell Extras

Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.Extras.Internal.Types

Contents

Description

Types used throughout the Extras package

Synopsis

Tagging

type Tag = Int Source #

Tags provide uniqueness for messages, so that they can be matched with their response.

type TagPool = MVar Tag Source #

Generates unique Tag for messages and response pairs. Each process that depends, directly or indirectly, on the call mechanisms in Control.Distributed.Process.Global.Call should have at most one TagPool on which to draw unique message tags.

newTagPool :: Process TagPool Source #

Create a new per-process source of unique message identifiers.

getTag :: TagPool -> Process Tag Source #

Extract a new identifier from a TagPool.

Addressing

class Linkable a where Source #

Class of things to which a Process can link itself.

Methods

linkTo :: Resolvable a => a -> Process () Source #

Create a link with the supplied object.

class Killable p where Source #

Class of things that can be killed (or instructed to exit).

Methods

killProc :: Resolvable p => p -> String -> Process () Source #

Kill (instruct to exit) generic process, using kill primitive.

exitProc :: (Resolvable p, Serializable m) => p -> m -> Process () Source #

Kill (instruct to exit) generic process, using exit primitive.

Instances

Resolvable p => Killable p Source # 

Methods

killProc :: p -> String -> Process () Source #

exitProc :: (Resolvable p, Serializable m) => p -> m -> Process () Source #

class Routable a where Source #

Class of things that you can route/send serializable message to

Methods

sendTo :: (Serializable m, Resolvable a) => a -> m -> Process () Source #

Send a message to the target asynchronously

unsafeSendTo :: (NFSerializable m, Resolvable a) => a -> m -> Process () Source #

Send some NFData message to the target asynchronously, forcing evaluation (i.e., deepseq) beforehand.

Instances

Routable String Source # 
Routable ProcessId Source # 
Routable Recipient Source # 
Routable LogClient Source # 
Routable LogChan Source # 
Routable (Message -> Process ()) Source # 

Methods

sendTo :: (Serializable m, Resolvable (Message -> Process ())) => (Message -> Process ()) -> m -> Process () Source #

unsafeSendTo :: (NFSerializable m, Resolvable (Message -> Process ())) => (Message -> Process ()) -> m -> Process () Source #

Routable (NodeId, String) Source # 

data Recipient Source #

A simple means of mapping to a receiver.

Instances

Eq Recipient Source # 
Show Recipient Source # 
Generic Recipient Source # 

Associated Types

type Rep Recipient :: * -> * #

Binary Recipient Source # 
NFData Recipient Source # 

Methods

rnf :: Recipient -> () #

Routable Recipient Source # 
Resolvable Recipient Source # 
type Rep Recipient Source # 

data RegisterSelf Source #

Used internally in whereisOrStart. Sent as (RegisterSelf,ProcessId).

Constructors

RegisterSelf 

Instances

Generic RegisterSelf Source # 

Associated Types

type Rep RegisterSelf :: * -> * #

Binary RegisterSelf Source # 
NFData RegisterSelf Source # 

Methods

rnf :: RegisterSelf -> () #

type Rep RegisterSelf Source # 
type Rep RegisterSelf = D1 (MetaData "RegisterSelf" "Control.Distributed.Process.Extras.Internal.Types" "distributed-process-extras-0.3.2-8M2JPG0xSQwTSM074rUzv" False) (C1 (MetaCons "RegisterSelf" PrefixI False) U1)

Interactions

whereisRemote :: NodeId -> String -> Process (Maybe ProcessId) Source #

A synchronous version of whereis, this monitors the remote node and returns Nothing if the node goes down (since a remote node failing or being non-contactible has the same effect as a process not being registered from the caller's point of view).

resolveOrDie :: Resolvable a => a -> String -> Process ProcessId Source #

resolve the Resolvable or die with specified msg plus details of what didn't resolve

data CancelWait Source #

Wait cancellation message.

Constructors

CancelWait 

Instances

Eq CancelWait Source # 
Show CancelWait Source # 
Generic CancelWait Source # 

Associated Types

type Rep CancelWait :: * -> * #

Binary CancelWait Source # 
NFData CancelWait Source # 

Methods

rnf :: CancelWait -> () #

type Rep CancelWait Source # 
type Rep CancelWait = D1 (MetaData "CancelWait" "Control.Distributed.Process.Extras.Internal.Types" "distributed-process-extras-0.3.2-8M2JPG0xSQwTSM074rUzv" False) (C1 (MetaCons "CancelWait" PrefixI False) U1)

type Channel a = (SendPort a, ReceivePort a) Source #

Simple representation of a channel.

data Shutdown Source #

A ubiquitous shutdown signal that can be used to maintain a consistent shutdown/stop protocol for any process that wishes to handle it.

Constructors

Shutdown 

Instances

Eq Shutdown Source # 
Show Shutdown Source # 
Generic Shutdown Source # 

Associated Types

type Rep Shutdown :: * -> * #

Methods

from :: Shutdown -> Rep Shutdown x #

to :: Rep Shutdown x -> Shutdown #

Binary Shutdown Source # 

Methods

put :: Shutdown -> Put #

get :: Get Shutdown #

putList :: [Shutdown] -> Put #

NFData Shutdown Source # 

Methods

rnf :: Shutdown -> () #

type Rep Shutdown Source # 
type Rep Shutdown = D1 (MetaData "Shutdown" "Control.Distributed.Process.Extras.Internal.Types" "distributed-process-extras-0.3.2-8M2JPG0xSQwTSM074rUzv" False) (C1 (MetaCons "Shutdown" PrefixI False) U1)

data ExitReason Source #

Provides a reason for process termination.

Constructors

ExitNormal

indicates normal exit

ExitShutdown

normal response to a Shutdown

ExitOther !String

abnormal (error) shutdown

Instances

Eq ExitReason Source # 
Show ExitReason Source # 
Generic ExitReason Source # 

Associated Types

type Rep ExitReason :: * -> * #

Binary ExitReason Source # 
NFData ExitReason Source # 

Methods

rnf :: ExitReason -> () #

type Rep ExitReason Source # 
type Rep ExitReason = D1 (MetaData "ExitReason" "Control.Distributed.Process.Extras.Internal.Types" "distributed-process-extras-0.3.2-8M2JPG0xSQwTSM074rUzv" False) ((:+:) (C1 (MetaCons "ExitNormal" PrefixI False) U1) ((:+:) (C1 (MetaCons "ExitShutdown" PrefixI False) U1) (C1 (MetaCons "ExitOther" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))))

newtype ServerDisconnected Source #

Given when a server is unobtainable.

Instances

Generic ServerDisconnected Source # 
Binary ServerDisconnected Source # 
NFData ServerDisconnected Source # 

Methods

rnf :: ServerDisconnected -> () #

type Rep ServerDisconnected Source # 
type Rep ServerDisconnected = D1 (MetaData "ServerDisconnected" "Control.Distributed.Process.Extras.Internal.Types" "distributed-process-extras-0.3.2-8M2JPG0xSQwTSM074rUzv" True) (C1 (MetaCons "ServerDisconnected" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DiedReason)))

class (NFData a, Serializable a) => NFSerializable a Source #

Introduces a class that brings NFData into scope along with Serializable, such that we can force evaluation. Intended for use with the UnsafePrimitives module (which wraps Control.Distributed.Process.UnsafePrimitives), and guarantees evaluatedness in terms of NFData. Please note that we cannot guarantee that an NFData instance will behave the same way as a Binary one with regards evaluation, so it is still possible to introduce unexpected behaviour by using unsafe primitives in this way.