om-legion-6.9.0.3: Legion Framework.
Safe HaskellSafe-Inferred
LanguageHaskell2010

OM.Legion

Description

Legion is framework for building clusters of homogenous nodes that must maintain a shared, replicated state.

For instance, maybe in order to scale a service you are using a partitioning strategy to direct traffic for users A-H to node 1, users I-Q to node 2, and R-Z to node 3. The partition table itself is something all the nodes have to agree on and would make an excellent candidate for the "shared, replicated state" managed by this framework.

To update the shared state, whatever it is, use:

Additionally, since Legion already has to understand about different nodes in the cluster, and how to talk to them, we provide a variety of tools to help facilitate inter-node communication:

  • cast: We support sending arbitrary messages to other peers without waiting on a response.
  • call: We support sending requests to other peers that block on a response.
  • broadcast: We support sending a message to _every_ other peer without waiting on a response
  • broadcall: We support sending a request to every other peer, and blocking until we recieve a response from them all.
Synopsis

Starting up the runtime.

forkLegionary Source #

Arguments

:: (EventConstraints e, MonadConstraints m) 
=> (ByteString -> IO ByteString)

Handle a user call request.

-> (ByteString -> IO ())

Handle a user cast message.

-> (Peer -> EventFold ClusterName Peer e -> IO ())

Callback when the cluster-wide eventfold changes.

-> Int

The propagation interval, in microseconds (for use with threadDelay).

-> StartupMode e

How to start the runtime, by creating new cluster or joining an existing cluster.

-> m (Runtime e) 

Fork the Legion runtime system.

type EventConstraints e = (Binary (Output e), Binary (State e), Binary e, Default (State e), Eq (Output e), Eq e, Event Peer e, Show (Output e), Show (State e), Show e, ToJSON (Output e), ToJSON (State e), ToJSON e) Source #

Shorthand for all the constraints needed for the event type. Mainly used so that documentation renders better.

type MonadConstraints m = (MonadCatch m, MonadFail m, MonadLoggerIO m, MonadTimeSpec m, MonadUnliftIO m, Race) Source #

Shorthand for all the monad constraints, mainly use so that documentation renders better.

data StartupMode e Source #

This defines the various ways a node can be spun up.

Constructors

NewCluster

Indicates that we should bootstrap a new cluster at startup.

Fields

  • Peer

    The peer being launched.

  • ClusterName

    The name of the cluster being launched.

JoinCluster

Indicates that the node should try to join an existing cluster.

Fields

  • Peer

    The peer being launched.

  • ClusterName

    The name of the cluster we are trying to join.

  • Peer

    The existing peer we are attempting to join with.

Recover

Resume operation given the previously saved state.

Fields

Instances

Instances details
(Show e, Show (Output e), Show (State e)) => Show (StartupMode e) Source # 
Instance details

Defined in OM.Legion.Runtime

data Runtime e Source #

A handle on the Legion runtime.

Instances

Instances details
Actor (Runtime e) Source # 
Instance details

Defined in OM.Legion.Runtime

Associated Types

type Msg (Runtime e) #

Methods

actorChan :: Runtime e -> Msg (Runtime e) -> IO () #

type Msg (Runtime e) Source # 
Instance details

Defined in OM.Legion.Runtime

type Msg (Runtime e)

Applying state changes.

applyFast Source #

Arguments

:: MonadIO m 
=> Runtime e

The runtime handle.

-> e

The event to be applied.

-> m (Output e)

Returns the possibly inconsistent event output.

Update the distributed cluster state by applying an event. The event output will be returned immediately and may not reflect a totally consistent view of the cluster. The state update itself, however, is guaranteed to be applied atomically and consistently throughout the cluster.

applyConsistent Source #

Arguments

:: MonadIO m 
=> Runtime e

The runtime handle.

-> e

The event to be applied.

-> m (Output e)

Returns the strongly consistent event output.

Update the distributed cluster state by applying an event. Both the event output and resulting state will be totally consistent throughout the cluster.

Sending messages around the cluster.

cast :: MonadIO m => Runtime e -> Peer -> ByteString -> m () Source #

Send a user message to some other peer, without waiting on a response.

call :: MonadIO m => Runtime e -> Peer -> ByteString -> m ByteString Source #

Send a user message to some other peer, and block until a response is received.

broadcast :: MonadIO m => Runtime e -> ByteString -> m () Source #

Send a user message to all peers, without wating on a response.

broadcall Source #

Arguments

:: MonadIO m 
=> Runtime e 
-> DiffTime

The timeout.

-> ByteString 
-> m (Map Peer (Maybe ByteString)) 

Send a user message to all peers, and block until a response is received from all of them.

Inspecting the current state.

readState :: MonadIO m => Runtime e -> m (EventFold ClusterName Peer e) Source #

Read the current powerstate value.

getSelf :: Runtime e -> Peer Source #

Get the identifier for the local peer.

Observability

getStats :: MonadIO m => Runtime e -> m Stats Source #

Retrieve some basic stats that can be used to intuit the health of the cluster.

newtype Stats Source #

Some basic stats that can be used to intuit the health of the cluster. We currently only report on how long it has been since some peer has made some progress.

Constructors

Stats 

Fields

  • timeWithoutProgress :: Map Peer DiffTime

    How long it has been since a Peer has made progress (if it is divergent). If the peer is completely up to date as far as we know, then it does not appear in the map at all. Only peers which we are expecting to make progress appear.

Instances

Instances details
ToJSON Stats Source # 
Instance details

Defined in OM.Legion.Runtime

Generic Stats Source # 
Instance details

Defined in OM.Legion.Runtime

Associated Types

type Rep Stats :: Type -> Type #

Methods

from :: Stats -> Rep Stats x #

to :: Rep Stats x -> Stats #

Show Stats Source # 
Instance details

Defined in OM.Legion.Runtime

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

Binary Stats Source # 
Instance details

Defined in OM.Legion.Runtime

Methods

put :: Stats -> Put #

get :: Get Stats #

putList :: [Stats] -> Put #

Eq Stats Source # 
Instance details

Defined in OM.Legion.Runtime

Methods

(==) :: Stats -> Stats -> Bool #

(/=) :: Stats -> Stats -> Bool #

type Rep Stats Source # 
Instance details

Defined in OM.Legion.Runtime

type Rep Stats = D1 ('MetaData "Stats" "OM.Legion.Runtime" "om-legion-6.9.0.3-inplace" 'True) (C1 ('MetaCons "Stats" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeWithoutProgress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Peer DiffTime))))

Cluster Topology

eject :: MonadIO m => Runtime e -> Peer -> m () Source #

Eject a peer from the cluster.

newtype Peer Source #

The identification of a node within the legion cluster.

Constructors

Peer 

Fields

Instances

Instances details
FromJSON Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

FromJSONKey Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

ToJSON Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

ToJSONKey Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

Show Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

Methods

showsPrec :: Int -> Peer -> ShowS #

show :: Peer -> String #

showList :: [Peer] -> ShowS #

Binary Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

Methods

put :: Peer -> Put #

get :: Get Peer #

putList :: [Peer] -> Put #

Eq Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

Methods

(==) :: Peer -> Peer -> Bool #

(/=) :: Peer -> Peer -> Bool #

Ord Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

Methods

compare :: Peer -> Peer -> Ordering #

(<) :: Peer -> Peer -> Bool #

(<=) :: Peer -> Peer -> Bool #

(>) :: Peer -> Peer -> Bool #

(>=) :: Peer -> Peer -> Bool #

max :: Peer -> Peer -> Peer #

min :: Peer -> Peer -> Peer #

FromHttpApiData Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

ToHttpApiData Peer Source # 
Instance details

Defined in OM.Legion.MsgChan

newtype ClusterName Source #

The name of a cluster.

Constructors

ClusterName 

Fields

Instances

Instances details
FromJSON ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

ToJSON ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

IsString ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

Show ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

Binary ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

Eq ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

Ord ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

FromHttpApiData ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan

ToHttpApiData ClusterName Source # 
Instance details

Defined in OM.Legion.MsgChan