crdt-event-fold-1.0.0.2: Garbage collected event folding CRDT.
Safe HaskellNone
LanguageHaskell2010

Data.CRDT.EventFold

Description

This module provides a CRDT data structure that collects and applies operations (called "events") that mutate an underlying data structure (like folding).

In addition to mutating the underlying data, each operation can also produce an output that can be obtained by the client. The output can be either totally consistent across all replicas (which is slower), or it can be returned immediately and possibly reflect an inconsistent state.

The EventFold name derives from a loose analogy to folding over a list of events using plain old foldl. The component parts of foldl are:

  • A binary operator, analogous to apply.
  • An accumulator value, analogous to infimumValue.
  • A list of values to fold over, loosely analogous to "the list of all future calls to event".
  • A return value. There is no real analogy for the "return value". Similarly to how you never actually obtain a return value if you try to foldl over an infinite list, EventFolds are meant to be long-lived objects that accommodate an infinite number of calls to event. What you can do is inspect the current value of the accumulator using infimumValue, or the "projected" value of the accumulator using projectedValue (where "projected" means "taking into account all of the currently known calls to event that have not yet been folded into the accumulator, and which may yet turn out to to have other events inserted into the middle or beginning of the list").

The EventFold value itself can be thought of as an intermediate, replicated, current state of the fold of an infinite list of events that has not yet been fully generated. So you can, for instance, check the current accumulator value.

In a little more detail, consider the type signature of foldl (for lists).

foldl
  :: (b -> a -> b) -- Analogous to 'apply', where 'a' is your 'Event'
                   -- instance, and 'b' is 'State a'.

  -> b             -- Loosely analogous to 'infimumValue' where
                   -- progressives applications are accumulated. (I
                   -- know that in the type signature of 'foldl'
                   -- this is the "starting value", but imagine that
                   -- for a recursive implementation of 'foldl',
                   -- the child call's "starting value" is the parent
                   -- call's accumulated value.)

  -> [a]           -- Analogous to all outstanding or future calls to
                   -- 'event'.

  -> b             
Synopsis

Basic API

Creating new CRDTs.

new Source #

Arguments

:: (Default (State e), Ord p) 
=> o

The "origin", iditifying the historical lineage of this CRDT.

-> p

The initial participant.

-> EventFold o p e 

Construct a new EventFold with the given origin and initial participant.

Adding new events.

event :: (Ord p, Event e) => p -> e -> EventFold o p e -> (Output e, EventId p, EventFold o p e) Source #

Introduce a change to the EventFold on behalf of the participant. Return the new EventFold, along with the projected output of the event, along with an EventId which can be used to get the fully consistent event output at a later time.

Coordinating replica updates.

Functions in this section are used to help merge foreign copies of the CRDT, and transmit our own copy. (This library does not provide any kind of transport support, except that all the relevant types have Binary instances. Actually arranging for these things to get shipped across a wire is left to the user.)

In principal, the only two functions you need are fullMerge and acknowledge. You can ship the full EventFold value to a remote participant and it can incorporate any changes using fullMerge, and vice versa. You can receive an EventFold value from another participant and incorporate its changes locally using fullMerge. You can then acknowledge the incorporation using acknowledge.

However, if your underlying data structure is large, it may be more efficient to just ship a sort of diff containing the information that the local participant thinks the remote participant might be missing. That is what events, mergeMaybe, and mergeEither are for.

Calling acknowledge is important because that is the magic that allows CRDT garbage collection to happen. "CRDT garbage collection" means we don't store an infinite series of events that always grows and never shrinks. We only store the outstanding events that we can't prove have been seen by every participant. Events that we can prove have been seen by every participant are applied to the infimum (a.k.a. "base value") and the event itself is discarded.

fullMerge :: (Eq o, Event e, Ord p) => EventFold o p e -> EventFold o p e -> Either (MergeError o p e) (EventFold o p e, Map (EventId p) (Output e)) Source #

Like mergeEither, but merge a full EventFold instead of just an event pack.

Returns the new EventFold value, along with the output for all of the events that can now be considered "fully consistent".

acknowledge :: (Event e, Ord p) => p -> EventFold o p e -> (EventFold o p e, Map (EventId p) (Output e)) Source #

Record the fact that the participant acknowledges the information contained in the EventFold. The implication is that the participant must base all future operations on the result of this function.

Returns the new EventFold value, along with the output for all of the events that can now be considered "fully consistent".

events :: Ord p => p -> EventFold o p e -> EventPack o p e Source #

Get the outstanding events that need to be propagated to a particular participant.

mergeMaybe :: (Eq o, Event e, Ord p) => EventFold o p e -> EventPack o p e -> Maybe (EventFold o p e, Map (EventId p) (Output e)) Source #

Monotonically merge the information in two EventFolds. The resulting EventFold may have a higher infimum value, but it will never have a lower one. Only EventFolds that originated from the same new call can be merged. If the origins are mismatched, then Nothing is returned.

Returns the new EventFold value, along with the output for all of the events that can now be considered "fully consistent".

mergeEither :: (Eq o, Event e, Ord p) => EventFold o p e -> EventPack o p e -> Either (MergeError o p e) (EventFold o p e, Map (EventId p) (Output e)) Source #

Like mergeMaybe, but returns an error indicating exactly what went wrong.

data MergeError o p e Source #

This is the exception type for illegal merges. These errors indicate a serious programming bugs.

Constructors

DifferentOrigins o o

The EventFolds do not have the same origin. It makes no sense to merge EventFolds that have different origins because they do not share a common history.

EventPackTooNew (EventFold o p e) (EventPack o p e)

The EventPack's infimum is greater than any event known to EventFold into which it is being merged. This should be impossible and indicates that either the local EventFold has rolled back an event that it had previously acknowledged, or else the source of the EventPack moved the infimum forward without a full acknowledgement from all participants. Both of these conditions should be regarded as serious bugs.

EventPackTooSparse (EventFold o p e) (EventPack o p e)

The EventPack assumes we know about events that we do not in fact know about. This is only possible if we rolled back our copy of the state somehow and "forgot" about state that we had previous acknowledged, or else some other participant erroneously acknowledged some events on our behalf.

Instances

Instances details
(Show (Output e), Show o, Show p, Show e, Show (State e)) => Show (MergeError o p e) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

showsPrec :: Int -> MergeError o p e -> ShowS #

show :: MergeError o p e -> String #

showList :: [MergeError o p e] -> ShowS #

Participation.

participate :: Ord p => p -> p -> EventFold o p e -> (EventId p, EventFold o p e) Source #

Allow a participant to join in the distributed nature of the EventFold. Return the EventId at which the participation is recorded, and the resulting EventFold. The purpose of returning the state is so that it can use it to tell when the participation event has reached the infimum.

disassociate :: Ord p => p -> p -> EventFold o p e -> EventFold o p e Source #

Indicate that a participant is removing itself from participating in the distributed EventFold.

Defining your state and events.

class Event e where Source #

Instances of this class define the particular "events" being "folded" over in a distributed fashion. In addition to the event type itself, there are a couple of type families which define the State into which folded events are accumulated, and the Output which application of a particular event can generate.

TL;DR: This is how users define their own custom operations.

Associated Types

type Output e Source #

type State e Source #

Methods

apply :: e -> State e -> EventResult e Source #

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

Instances

Instances details
Event () Source #

The most trivial event type.

Instance details

Defined in Data.CRDT.EventFold

Associated Types

type Output () Source #

type State () Source #

Methods

apply :: () -> State () -> EventResult () Source #

(Event a, Event b) => Event (Either a b) Source #

The union of two event types.

Instance details

Defined in Data.CRDT.EventFold

Associated Types

type Output (Either a b) Source #

type State (Either a b) Source #

Methods

apply :: Either a b -> State (Either a b) -> EventResult (Either a b) Source #

data EventResult e Source #

The result of applying an event.

Morally speaking, events are always pure functions. However, mundane issues like finite memory constraints and finite execution time can cause referentially opaque behavior. In a normal Haskell program, this usually leads to a crash or an exception, and the crash or exception can itself, in a way, be thought of as being referentially transparent, because there is no way for it to both happen and, simultaneously, not happen.

However, in our case we are replicating computations across many different pieces of hardware, so there most definitely is a way for these aberrant system failures to both happen and not happen simultaneously. What happens if the computation of the event runs out of memory on one machine, but not on another?

There exists a strategy for dealing with these problems: if the computation of an event experiences a failure on every participant, then the event is pushed into the infimum as a failure (i.e. a no-op), but if any single participant successfully computes the event then all other participants can (somehow) request a "Full Merge" from the successful participant. The Full Merge will include the infimum value computed by the successful participant, which will include the successful application of the problematic event. The error participants can thus bypass computation of the problem event altogether, and can simply overwrite their infimum with the infimum provided by the Full Merge.

Doing a full merge can be much more expensive than doing a simple EventPack merge, because it requires transmitting the full value of the EventFold instead of just the outstanding operations.

This type represents how computation of the event finished; with either a pure result, or some kind of system error.

In general SystemError is probably only ever useful for when your event type somehow executes untrusted code (for instance when your event type is a Turing-complete DSL that allows users to submit their own custom-programmed "events") and you want to limit the resources that can be consumed by such user-generated code. It is much less useful when you are encoding some well defined business logic directly in Haskell.

Constructors

SystemError (Output e) 
Pure (Output e) (State e) 

Inspecting the EventFold.

isBlockedOnError :: EventFold o p e -> Bool Source #

Return True if progress on the EventFold is blocked on a SystemError.

projectedValue :: Event e => EventFold o p e -> State e Source #

Return the current projected value of the EventFold.

infimumValue :: EventFoldF o p e f -> State e Source #

Return the current infimum value of the EventFold.

infimumId :: EventFoldF o p e f -> EventId p Source #

Return the EventId of the infimum value.

infimumParticipants :: EventFoldF o p e f -> Set p Source #

Gets the known participants at the infimum.

allParticipants :: Ord p => EventFold o p e -> Set p Source #

Get all known participants. This includes participants that are projected for removal.

projParticipants :: Ord p => EventFold o p e -> Set p Source #

Get all the projected participants. This does not include participants that are projected for removal.

origin :: EventFoldF o p e f -> o Source #

Return the origin value of the EventFold.

divergent :: forall o p e. Ord p => EventFold o p e -> Map p (EventId p) Source #

Returns the participants that we think might be diverging. In this context, a participant is "diverging" if there is an event that the participant has not acknowledged but we are expecting it to acknowledge. Along with the participant, return the last known EventId which that participant has acknowledged.

Underlying Types

data EventFoldF o p e f Source #

This represents a replicated data structure into which participants can add Events that are folded into a base State. You can also think of the "events" as operations that mutate the base state, and the point of this CRDT is to coordinate the application of the operations across all participants so that they are applied consistently even if the operations themselves are not commutative, idempotent, or monotonic. Those properties to the CRDT by the way in which it manages the events, and it is therefore unnecessary that the events themselves have them.

Variables are:

  • o - Origin
  • p - Participant
  • e - Event
  • f - The Monad in which the events live

The Origin is a value that is more or less meant to identify the "thing" being replicated, and in particular identify the historical lineage of the EventFold. The idea is that it is meaningless to try and merge two EventFolds that do not share a common history (identified by the origin value) and doing so is a programming error. It is only used to try and check for this type of programming error and throw an exception if it happens instead of producing undefined (and difficult to detect) behavior.

Instances

Instances details
(Eq (f (Delta p e)), Eq (Output e), Eq o, Eq p, Eq e) => Eq (EventFoldF o p e f) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

(==) :: EventFoldF o p e f -> EventFoldF o p e f -> Bool #

(/=) :: EventFoldF o p e f -> EventFoldF o p e f -> Bool #

(Show (f (Delta p e)), Show o, Show p, Show (State e)) => Show (EventFoldF o p e f) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

showsPrec :: Int -> EventFoldF o p e f -> ShowS #

show :: EventFoldF o p e f -> String #

showList :: [EventFoldF o p e f] -> ShowS #

Generic (EventFoldF o p e f) Source # 
Instance details

Defined in Data.CRDT.EventFold

Associated Types

type Rep (EventFoldF o p e f) :: Type -> Type #

Methods

from :: EventFoldF o p e f -> Rep (EventFoldF o p e f) x #

to :: Rep (EventFoldF o p e f) x -> EventFoldF o p e f #

(Binary (f (Delta p e)), Binary o, Binary p, Binary e, Binary (State e), Binary (Output e)) => Binary (EventFoldF o p e f) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

put :: EventFoldF o p e f -> Put #

get :: Get (EventFoldF o p e f) #

putList :: [EventFoldF o p e f] -> Put #

type Rep (EventFoldF o p e f) Source # 
Instance details

Defined in Data.CRDT.EventFold

type Rep (EventFoldF o p e f)

type EventFold o p e = EventFoldF o p e Identity Source #

data EventId p Source #

EventId is a monotonically increasing, totally ordered identification value which allows us to lend the attribute of monotonicity to event application operations which would not naturally be monotonic.

Instances

Instances details
Eq p => Eq (EventId p) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

(==) :: EventId p -> EventId p -> Bool #

(/=) :: EventId p -> EventId p -> Bool #

Ord p => Ord (EventId p) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

compare :: EventId p -> EventId p -> Ordering #

(<) :: EventId p -> EventId p -> Bool #

(<=) :: EventId p -> EventId p -> Bool #

(>) :: EventId p -> EventId p -> Bool #

(>=) :: EventId p -> EventId p -> Bool #

max :: EventId p -> EventId p -> EventId p #

min :: EventId p -> EventId p -> EventId p #

Show p => Show (EventId p) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

showsPrec :: Int -> EventId p -> ShowS #

show :: EventId p -> String #

showList :: [EventId p] -> ShowS #

Generic (EventId p) Source # 
Instance details

Defined in Data.CRDT.EventFold

Associated Types

type Rep (EventId p) :: Type -> Type #

Methods

from :: EventId p -> Rep (EventId p) x #

to :: Rep (EventId p) x -> EventId p #

Binary p => Binary (EventId p) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

put :: EventId p -> Put #

get :: Get (EventId p) #

putList :: [EventId p] -> Put #

Default (EventId p) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

def :: EventId p #

type Rep (EventId p) Source # 
Instance details

Defined in Data.CRDT.EventFold

type Rep (EventId p) = D1 ('MetaData "EventId" "Data.CRDT.EventFold" "crdt-event-fold-1.0.0.2-inplace" 'False) (C1 ('MetaCons "BottomEid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word256) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 p)))

data EventPack o p e Source #

A package containing events that can be merged into an event fold.

Instances

Instances details
(Show o, Show p, Show e, Show (Output e)) => Show (EventPack o p e) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

showsPrec :: Int -> EventPack o p e -> ShowS #

show :: EventPack o p e -> String #

showList :: [EventPack o p e] -> ShowS #

Generic (EventPack o p e) Source # 
Instance details

Defined in Data.CRDT.EventFold

Associated Types

type Rep (EventPack o p e) :: Type -> Type #

Methods

from :: EventPack o p e -> Rep (EventPack o p e) x #

to :: Rep (EventPack o p e) x -> EventPack o p e #

(Binary o, Binary p, Binary e, Binary (Output e)) => Binary (EventPack o p e) Source # 
Instance details

Defined in Data.CRDT.EventFold

Methods

put :: EventPack o p e -> Put #

get :: Get (EventPack o p e) #

putList :: [EventPack o p e] -> Put #

type Rep (EventPack o p e) Source # 
Instance details

Defined in Data.CRDT.EventFold

type Rep (EventPack o p e)