legion-0.9.0.2: Distributed, stateful, homogeneous microservice framework.

Safe HaskellNone
LanguageHaskell2010

Network.Legion

Contents

Description

Legion is a mathematically sound framework for writing horizontally scalable business logic, or applications. Historically, horizontal scalability has been achieved via the property of statelessness. Programmers would design their applications to be free of any kind of persistent state, avoiding the problem of distributed state management. This almost never turns out to really be possible, so programmers achieve "statelessness" by delegating application state management to some kind of external, shared database (which ends up having its own scalability problems).

In addition to scalability problems, which modern databases (especially NoSQL databases) have done a good job of solving, there is another, more fundamental problem facing these architectures: The application is not really stateless.

Legion is a Haskell framework that abstracts state partitioning, data replication, request routing, and cluster rebalancing, making it easy to implement large and robust distributed stateful applications.

Synopsis

API Reference

Starting the Legion Runtime

forkLegionary Source #

Arguments

:: (LegionConstraints e o s, MonadLoggerIO io) 
=> Persistence e o s

The persistence layer used to back the legion framework.

-> RuntimeSettings

Settings and configuration of the legion framework.

-> StartupMode 
-> io (Runtime e o) 

Forks the legion framework in a background thread, and returns a way to send user requests to it and retrieve the responses to those requests.

  • e is the type of request your application will handle. e stands for "event".
  • o is the type of response produced by your application. o stands for "output"
  • s is the type of state maintained by your application. More precisely, it is the type of the individual partitions that make up your global application state. s stands for "state".

data StartupMode Source #

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

Constructors

NewCluster

Indicates that we should bootstrap a new cluster at startup.

JoinCluster SockAddr

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

Recover Peer ClusterPowerState

Recover from a crash as the given peer, using the given cluster state.

data Runtime e o Source #

This type represents a handle to the runtime environment of your Legion application. This allows you to make requests and access the partition index.

Runtime is an opaque structure. Use makeRequest and search to access it.

Making Runtime Requests

makeRequest :: MonadIO io => Runtime e o -> PartitionKey -> e -> io o Source #

Send a user request to the legion runtime.

search :: MonadIO io => Runtime e o -> SearchTag -> Source io IndexRecord Source #

Send a search request to the legion runtime. Returns results that are strictly greater than the provided SearchTag.

Application Definition

type LegionConstraints e o s = (Event e o s, Indexable s, Binary e, Binary o, Binary s, Default s, Eq e, Show e, Show o, Show s) Source #

This is a more convenient way to write the somewhat unwieldy set of constraints

(
  Event e o s,
  Indexable s,
  Binary e,
  Binary o,
  Binary s,
  Default s,
  Eq e,
  Show e,
  Show o,
  Show s
)

The ToJSON s requirement is strictly for servicing the admin web endpoints.

data Persistence e o s Source #

The type of a user-defined persistence strategy used to persist partition states. See newMemoryPersistence or diskPersistence if you need to get started quickly.

Constructors

Persistence 

Fields

class Event e o s | e -> s o where Source #

The class which allows for event application.

Minimal complete definition

apply

Methods

apply :: e -> s -> (o, s) Source #

Apply an event to a state value. *This function MUST be total!!!*

Runtime Configuration

The legion framework has several operational parameters which can be controlled using configuration. These include the address binding used to expose the cluster management service endpoint and what file to use for cluster state journaling. To get started quickly, consider using legion-extra:Network.Legion.Config

data RuntimeSettings Source #

Settings used when starting up the legion framework runtime.

Constructors

RuntimeSettings 

Fields

  • peerBindAddr :: SockAddr

    The address on which the legion framework will listen for rebalancing and cluster management commands.

  • joinBindAddr :: SockAddr

    The address on which the legion framework will listen for cluster join requests.

  • adminHost :: HostPreference

    The host address on which the admin service should run.

  • adminPort :: Port

    The host port on which the admin service should run.

Indexing

class Indexable s where Source #

This typeclass provides the ability to index partition states.

Minimal complete definition

indexEntries

Methods

indexEntries :: s -> Set Tag Source #

A way of indexing partitions so that they can be found without knowing the partition key. An index entry for the partition will be created under each of the tags returned by this function.

newtype Tag Source #

A tag is a value associated with a partition state that can be used to look up a partition key.

Constructors

Tag 

Fields

Instances

Eq Tag Source # 

Methods

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

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

Ord Tag Source # 

Methods

compare :: Tag -> Tag -> Ordering #

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

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

(>) :: Tag -> Tag -> Bool #

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

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

IsString Tag Source # 

Methods

fromString :: String -> Tag #

Binary Tag Source # 

Methods

put :: Tag -> Put #

get :: Get Tag #

putList :: [Tag] -> Put #

data SearchTag Source #

This data structure describes where in the index to start scrolling.

Constructors

SearchTag 

data IndexRecord Source #

This data structure describes a record in the index.

Constructors

IndexRecord 

Fields

Instances

Eq IndexRecord Source # 
Ord IndexRecord Source # 
Show IndexRecord Source # 
Generic IndexRecord Source # 

Associated Types

type Rep IndexRecord :: * -> * #

ToJSON IndexRecord Source # 
Binary IndexRecord Source # 
type Rep IndexRecord Source # 
type Rep IndexRecord = D1 (MetaData "IndexRecord" "Network.Legion.Index" "legion-0.9.0.2-8FnWIGM2bbf9QhFKEmxUW5" False) (C1 (MetaCons "IndexRecord" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "irTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Tag)) (S1 (MetaSel (Just Symbol "irKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartitionKey))))

Other Types

data Peer Source #

The way to identify a peer.

Instances

Eq Peer Source # 

Methods

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

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

Ord Peer Source # 

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 #

Read Peer Source # 
Show Peer Source # 

Methods

showsPrec :: Int -> Peer -> ShowS #

show :: Peer -> String #

showList :: [Peer] -> ShowS #

Binary Peer Source # 

Methods

put :: Peer -> Put #

get :: Get Peer #

putList :: [Peer] -> Put #

newtype PartitionKey Source #

This is how partitions are identified and referenced.

Constructors

K 

Fields

type PartitionPowerState e o s = PowerState PartitionKey s Peer e o Source #

A representation of all possible partition states.

type ClusterPowerState = PowerState UUID ClusterState Peer Update () Source #

A representation of all possible cluster states.

Implementing a Legion Application

Implementing a Legion application boils down to two things: providing a persistence layer (see the legion-extra package for some pre-packaged persistence layers), and implementing all of the typeclasses in LegionConstraints, of which Event is the most important.

Take a look at Network.Legion.Discovery.LegionApp for a good example of how to build a core Legion application.

Typclasses to Implement

Lets take a look at LegionConstraints:

(
  Event e o s,
  Indexable s,
  
  Binary e, Binary o, Binary s, Default s, Eq e, Show e, Show o, Show s
)

First, a note on the type variables uesd:

  • e is the type of request your application will handle. e stands for "event".
  • o is the type of response produced by your application. o stands for "output"
  • s is the type of state maintained by your application. More precisely, it is the type of the individual partitions that make up your global application state. s stands for "state".

The two most important typeclasses here are Event and Indexable. The rest are mainly used for implementation details, like packaging up data to send over the network, and constructing log messages, etc.

Event

Your Event instance will serve as the core of your application. If you think of your application as a large state machine, with inputs, state changes and outputs, then the Event typeclass acts as the main state transition function.

class Event e o s | e -> s o where
  apply :: e -> s -> (o, s)

The apply function acts like a state transition function. It handles application inputs (which are the events themselves), state transitions, and outputs. In other words, your Event instance is your legion application.

You will notice that the apply function is totally pure. The idea is that Legion will handle all of the necessary IO. It will push events around on the network. It will retrieve state from the persistence layer and automatically invoke your apply function where appropriate. This purity is necessary because it is the nature of distributed, replicated systems that the order of events may sometimes need to be rearranged, and the events themselves will have to be replicated, and therefore applied more than once (at least one time for each replica).

Indexable

The next important typeclass is Indexable.

class Indexable s where
  indexEntries :: s -> Set Tag

For handling regular requests using makeRequest, you must know the key of the partition you are looking for a priori. Sometimes, though, you want to look up some unknown set of partitions based on another attribute. The most basic example is when you want to do a simple listing of all the partition keys in the system.

This is where the indexing system and the search function come in. The indexing system is exposed at a relatively low level of abstraction because the use cases for which it is needed will vary wildly from application to application. There is only a single global index, but each partition may produce zero to many records in that index. This is what the Set Tag portion of the type signature above is all about.

Conceptually, the "index" is a single, global, ordered list of IndexRecords. The search function allows you to scroll forward through this list at will.

Indexing is implemented by instantiating the Indexable typeclass for your state type.

The tags returned by indexEntries are used to construct a set of zero or more IndexRecords. For each Tag returned by indexEntries, an IndexRecord is generated such that:

IndexRecord {irTag = <your tag>, irKey = <partition key>}

Exposing Your Application

The interface to your new application is a Haskell api, which isn't very useful on its own. You are usually going to want to provide a wrapper around your core Legion app so that it is accessible to the outside world. The Legion-Discovery application uses Servant to expose its core Legion application via a web interface.

Partitions, Explained

Coming soon.

The Persistence Layer

Coming soon.