distributed-process-extras-0.3.5: Cloud Haskell Extras

Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.Extras

Contents

Description

Cloud Haskell Extras
Evaluation Strategies and Support for NFData

When sending messages to a local process (i.e., intra-node), the default approach is to encode (i.e., serialise) the message anyway, just to ensure that no unevaluated thunks are passed to the receiver. In distributed-process, you must explicitly choose to use unsafe primitives that do nothing to ensure evaluation, since this might cause an error in the receiver which would be difficult to debug. Using NFData, it is possible to force evaluation, but there is no way to ensure that both the NFData and Binary instances do so in the same way (i.e., to the same depth, etc) therefore automatic use of NFData is not possible in distributed-process.

By contrast, distributed-process-platform makes extensive use of NFData to force evaluation (and avoid serialisation overheads during intra-node communication), via the NFSerializable type class. This does nothing to fix the potential disparity between NFData and Binary instances, so you should verify that your data is being handled as expected (e.g., by sticking to strict fields, or some such) and bear in mind that things could go wrong.

The UnsafePrimitives module in this library will force evaluation before calling the UnsafePrimitives in distributed-process, which - if you've vetted everything correctly - should provide a bit more safety, whilst still keeping performance at an acceptable level.

Users of the various service and utility models (such as ManagedProcess and the Service and Task APIs) should consult the sub-system specific documentation for instructions on how to utilise these features.

IMPORTANT NOTICE: Despite the apparent safety of forcing evaluation before sending, we still cannot make any actual guarantees about the evaluation semantics of these operations, and therefore the unsafe moniker will remain in place, in one form or another, for all functions and modules that use them.

Addressing/Interaction Tools

The various type classes exposed here, along with some common data types (such as Shutdown, ServerDisconnected, etc.) are intended to simplify your CH programs, and facilitate easily plugging code into higher level libraries such as distributed-process-client-server and distributed-process-supervisor.

Error/Exception Handling

It is important not to be too general when catching exceptions in cloud haskell application, because asynchonous exceptions provide cloud haskell with its process termination mechanism. Two exception types in particular, signal the instigator's intention to stop a process immediately, which are raised (i.e., thrown) in response to the kill and exit primitives provided by the base distributed-process package.

You should generally try to keep exception handling code to the lowest (i.e., most specific) scope possible. If you wish to trap exit signals, use the various flavours of catchExit primitive from distributed-process.

Synopsis

Exported Types

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 # 

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 (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.

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 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.5-7qzKH0dWmcLBNm6JMkdrjz" 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.5-7qzKH0dWmcLBNm6JMkdrjz" 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)))))

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.5-7qzKH0dWmcLBNm6JMkdrjz" False) (C1 * (MetaCons "CancelWait" PrefixI False) (U1 *))

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.5-7qzKH0dWmcLBNm6JMkdrjz" True) (C1 * (MetaCons "ServerDisconnected" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DiedReason)))

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

Simple representation of a channel.

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.

Primitives overriding those in distributed-process

monitor :: Resolvable a => a -> Process (Maybe MonitorRef) Source #

Monitor any Resolvable object.

Utilities and Extended Primitives

spawnSignalled :: Process a -> (a -> Process ()) -> Process ProcessId Source #

Spawn a new (local) process. This variant takes an initialisation action and a secondary expression from the result of the initialisation to Process (). The spawn operation synchronises on the completion of the before action, such that the calling process is guaranteed to only see the newly spawned ProcessId once the initialisation has successfully completed.

spawnLinkLocal :: Process () -> Process ProcessId Source #

Node local version of spawnLink. Note that this is just the sequential composition of spawn and link. (The Unified semantics that underlies Cloud Haskell does not even support a synchronous link operation)

spawnMonitorLocal :: Process () -> Process (ProcessId, MonitorRef) Source #

Like spawnLinkLocal, but monitors the spawned process.

linkOnFailure :: ProcessId -> Process () Source #

CH's link primitive, unlike Erlang's, will trigger when the target process dies for any reason. This function has semantics like Erlang's: it will trigger ProcessLinkException only when the target dies abnormally.

times :: Int -> Process () -> Process () Source #

Deprecated: use replicateM_ instead

Apply the supplied expression n times

isProcessAlive :: ProcessId -> Process Bool Source #

Check if specified process is alive. Information may be outdated.

matchCond :: Serializable a => (a -> Maybe (Process b)) -> Match b Source #

An alternative to matchIf that allows both predicate and action to be expressed in one parameter.

deliver :: (Addressable a, Serializable m) => m -> a -> Process () Source #

Send message to Addressable object.

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

Wait until Resolvable object will exit. Return immediately if object can't be resolved.

awaitResponse :: Addressable a => a -> [Match (Either ExitReason b)] -> Process (Either ExitReason b) Source #

Safe (i.e., monitored) waiting on an expected response/message.

Call/Tagging support

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.

Registration and Process Lookup

whereisOrStart :: String -> Process () -> Process ProcessId Source #

Returns the pid of the process that has been registered under the given name. This refers to a local, per-node registration, not global registration. If that name is unregistered, a process is started. This is a handy way to start per-node named servers.

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

A remote equivalent of whereisOrStart. It deals with the node registry on the given node, and the process, if it needs to be started, will run on that node. If the node is inaccessible, Nothing will be returned.