Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- new :: forall o p e. (Default (State e), Event p e, Ord p) => o -> p -> EventFold o p e
- event :: forall o p e. (Event p e, Ord p) => p -> e -> EventFold o p e -> (Output e, EventId p, UpdateResult o p e)
- fullMerge :: (Eq (Output e), Eq e, Eq o, Event p e, Ord p) => p -> EventFold o p e -> EventFold o p e -> Either (MergeError o p e) (UpdateResult o p e)
- fullMerge_ :: (Eq (Output e), Eq e, Eq o, Event p e, Ord p) => EventFold o p e -> EventFold o p e -> Either (MergeError o p e) (UpdateResult o p e)
- data UpdateResult o p e = UpdateResult {
- urEventFold :: EventFold o p e
- urOutputs :: Map (EventId p) (Output e)
- urNeedsPropagation :: Bool
- events :: forall o p e. Ord p => p -> EventFold o p e -> Maybe (Diff o p e)
- diffMerge :: (Eq (Output e), Eq e, Eq o, Event p e, Ord p) => p -> EventFold o p e -> Diff o p e -> Either (MergeError o p e) (UpdateResult o p e)
- diffMerge_ :: forall o p e. (Eq (Output e), Eq e, Eq o, Event p e, Ord p) => EventFold o p e -> Diff o p e -> Either (MergeError o p e) (UpdateResult o p e)
- data MergeError o p e
- = DifferentOrigins o o
- | DiffTooNew (EventFold o p e) (Diff o p e)
- | DiffTooSparse (EventFold o p e) (Diff o p e)
- acknowledge :: (Eq (Output e), Eq e, Eq o, Event p e, Ord p) => p -> EventFold o p e -> UpdateResult o p e
- participate :: forall o p e. (Event p e, Ord p) => p -> p -> EventFold o p e -> (EventId p, UpdateResult o p e)
- disassociate :: forall o p e. (Event p e, Ord p) => p -> EventFold o p e -> (EventId p, UpdateResult o p e)
- class Event p e where
- data EventResult e
- = SystemError (Output e)
- | Pure (Output e) (State e)
- isBlockedOnError :: EventFold o p e -> Bool
- projectedValue :: forall o p e. Event p e => EventFold o p e -> State e
- infimumValue :: EventFold o p e -> State e
- infimumId :: EventFold o p e -> EventId p
- infimumParticipants :: EventFold o p e -> Set p
- allParticipants :: Ord p => EventFold o p e -> Set p
- projParticipants :: Ord p => EventFold o p e -> Set p
- origin :: EventFold o p e -> o
- divergent :: forall o p e. Ord p => EventFold o p e -> Map p (EventId p)
- source :: EventId p -> Maybe p
- data EventFold o p e
- data EventId p
- bottomEid :: EventId p
- data Diff o p e
Overview
This module provides a CRDT data structure that collects and applies operations (called "events") that mutate an underlying data structure.
It is "Garbage Collected" in the sense that the number of operations accumulated in the structure will not grow unbounded, assuming that participants manage to sync their data once in a while. The size of the data (as measured by the number of operations we have to store) is allowed to shrink.
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.
Garbage Collection
Unlike many traditional CRDTs which always grow and never shrink,
EventFold
has a mechanism for determining what consensus
has been reached by all of the participants, which allows us to
"garbage collect" events that achieved total consensus. Perhaps more
importantly, this allows us to produce the totally consistent output
for events for which total consensus has been achieved.
But there are trade offs. The big downside is that participation in the
distributed replication of the EventFold
must be strictly managed.
- The process of participating itself involves registering with an
existing participant, using
participate
. You can't just send the data off to some other computer and expect that now that computer is participating in the CRDT. It isn't. - Participants can not "restore from backup". Once they have incorporated data received from other participants or generated new data themselves, and that data has been transmitted to any other participant, they are committed to using that result going forward. Doing anything that looks like "restoring from an older version" would destroy the idea that participants have reached consensus on anything, and the results would be undefined and almost certainly completely wrong. This library is written with some limited capability to detect this situation, but it is not always possible to detect it all cases. Many times you will just end up with undefined behavior.
A Belabored Analogy
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,EventFold
s are meant to be long-lived objects that accommodate an infinite number of calls toevent
. What you can do is inspect the current value of the accumulator usinginfimumValue
, or the "projected" value of the accumulator usingprojectedValue
(where "projected" means "taking into account all of the currently known calls toevent
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 -- progressive applications are accumulated. -> [a] -- Analogous to all outstanding or future calls to -- 'event'. -> b
Basic API
Creating new CRDTs
:: forall o p e. (Default (State e), Event p e, Ord p) | |
=> o | The "origin", identifying 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 :: forall o p e. (Event p e, Ord p) => p -> e -> EventFold o p e -> (Output e, EventId p, UpdateResult o p e) Source #
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 function you need is fullMerge
. Everything
else in this section is an optimization. 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
.
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
and diffMerge
are for.
:: (Eq (Output e), Eq e, Eq o, Event p e, Ord p) | |
=> p | The "local" participant doing the merge. |
-> EventFold o p e | The local copy of the |
-> EventFold o p e | The remote copy of the |
-> Either (MergeError o p e) (UpdateResult o p e) |
Monotonically merge the information in two EventFold
s. The resulting
EventFold
may have a higher infimum value, but it will never have a
lower one (where "higher" and "lower" are measured by infimumId
value,
not the value of the underlying data structure). Only EventFold
s
that originated from the same new
call can be merged. If the origins
are mismatched, or if there is some other programming error detected,
then an error will be returned.
Returns the new EventFold
value, along with the output for all of
the events that can now be considered "fully consistent".
:: (Eq (Output e), Eq e, Eq o, Event p e, Ord p) | |
=> EventFold o p e | The local copy of the |
-> EventFold o p e | The remote copy of the |
-> Either (MergeError o p e) (UpdateResult o p e) |
Like fullMerge
, but without the automatic acknowlegement.
data UpdateResult o p e Source #
The result updating the EventFold
, which contains:
- The new
EventFold
value, - The outputs of events that have reached the infimum as a result of the update (i.e. "totally consistent outputs"),
- And a flag indicating whether the other participants need to hear about the changes.
Instances
(Show (Output e), Show (State e), Show e, Show o, Show p) => Show (UpdateResult o p e) Source # | |
Defined in Data.CRDT.EventFold showsPrec :: Int -> UpdateResult o p e -> ShowS # show :: UpdateResult o p e -> String # showList :: [UpdateResult o p e] -> ShowS # |
:: forall o p e. Ord p | |
=> p | The participant to which we are sending the |
-> EventFold o p e | The EventFold being propagated. |
-> Maybe (Diff o p e) |
|
Get the outstanding events that need to be propagated to a particular participant.
It isn't always the case that a less expensive diffMerge
is sufficient
to maintain consistency. For instance, if the initial participate
for a participant hasn't reached the infimum yet then there is no way
to guarantee that the target will receive every new event from every
participant (because an old participant might not even know about the
new participant, because being part of the infimum is the definition
of all participants knowing a thing).
If the new participant doesn't receive every event, then it obviously
can't apply
the missing events. Therefore, until it's participate
event is part of the infimum, it must receive infimum values that have
the missing events pre-applied by some other participant.
:: forall o p e. (Eq (Output e), Eq e, Eq o, Event p e, Ord p) | |
=> EventFold o p e | The local copy of the |
-> Diff o p e | The |
-> Either (MergeError o p e) (UpdateResult o p e) |
Like diffMerge
, but without automatic acknowledgement.
data MergeError o p e Source #
This is the exception type for illegal merges. These errors indicate serious programming bugs.
DifferentOrigins o o | The |
DiffTooNew (EventFold o p e) (Diff o p e) | The |
DiffTooSparse (EventFold o p e) (Diff o p e) | The |
Instances
acknowledge :: (Eq (Output e), Eq e, Eq o, Event p e, Ord p) => p -> EventFold o p e -> UpdateResult o p 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".
Participation
:: forall o p e. (Event p e, Ord p) | |
=> p | The local participant. |
-> p | The participant being added. |
-> EventFold o p e | |
-> (EventId p, UpdateResult o p e) |
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
EventId
is so that you can use it to tell when the participation
event has reached the infimum. See also: infimumId
:: forall o p e. (Event p e, Ord p) | |
=> p | The peer removing itself from participation. |
-> EventFold o p e | |
-> (EventId p, UpdateResult o p e) |
Indicate that a participant is removing itself from participating in
the distributed EventFold
.
Defining your state and events
class Event p 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.
apply :: e -> State e -> EventResult e Source #
Apply an event to a state value. **This function MUST be total!!!**
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
Diff
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.
TL;DR:
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 untrusted code. It is much less useful when
you are encoding some well defined business logic directly in Haskell.
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
.
The implication here is that if the local copy is blocked on a
SystemError
, it needs to somehow arrange for remote copies to send
full EventFold
s, not just Diff
s. A diffMerge
is not sufficient
to get past the block. Only a fullMerge
will suffice.
If your system is not using SystemError
or else not using Diff
s,
then you don't ever need to worry about this function.
projectedValue :: forall o p e. Event p e => EventFold o p e -> State e Source #
Return the current projected value of the EventFold
.
infimumValue :: EventFold o p e -> State e Source #
Return the current infimum value of the EventFold
.
infimumParticipants :: EventFold o p e -> 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.
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, or BottomEid
if the participant has a acknowledged no events, as may be the case
immediately after the participant joined replication.
source :: EventId p -> Maybe p Source #
The participant the created an event, if there is one (which there
isn't for bottomEid
).
Underlying Types
This type is a
CRDT
into which participants can add Event
s 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.
Variables are:
o
- Originp
- Participante
- Event
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 EventFold
s 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
(Ord p, FromJSON o, FromJSON p, FromJSON e, FromJSON (Output e), FromJSON (State e)) => FromJSON (EventFold o p e) Source # | |
Defined in Data.CRDT.EventFold | |
(ToJSON o, ToJSON p, ToJSON e, ToJSON (State e), ToJSON (Output e)) => ToJSON (EventFold o p e) Source # | |
Generic (EventFold o p e) Source # | |
(Show (Output e), Show o, Show p, Show e, Show (State e)) => Show (EventFold o p e) Source # | |
(Binary o, Binary p, Binary e, Binary (State e), Binary (Output e)) => Binary (EventFold o p e) Source # | |
(Eq (Output e), Eq o, Eq p, Eq e) => Eq (EventFold o p e) Source # | |
type Rep (EventFold o p e) Source # | |
Defined in Data.CRDT.EventFold |
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
FromJSON p => FromJSON (EventId p) Source # | |
Defined in Data.CRDT.EventFold | |
FromJSON p => FromJSONKey (EventId p) Source # | |
Defined in Data.CRDT.EventFold fromJSONKey :: FromJSONKeyFunction (EventId p) # | |
ToJSON p => ToJSON (EventId p) Source # | |
ToJSON p => ToJSONKey (EventId p) Source # | |
Defined in Data.CRDT.EventFold toJSONKey :: ToJSONKeyFunction (EventId p) # toJSONKeyList :: ToJSONKeyFunction [EventId p] # | |
Generic (EventId p) Source # | |
Show p => Show (EventId p) Source # | |
Binary p => Binary (EventId p) Source # | |
Default (EventId p) Source # | |
Defined in Data.CRDT.EventFold | |
Eq p => Eq (EventId p) Source # | |
Ord p => Ord (EventId p) Source # | |
Defined in Data.CRDT.EventFold | |
type Rep (EventId p) Source # | |
Defined in Data.CRDT.EventFold |
A package containing events that can be merged into an event fold.
Instances
(Ord p, FromJSON o, FromJSON p, FromJSON e, FromJSON (Output e)) => FromJSON (Diff o p e) Source # | |
Defined in Data.CRDT.EventFold | |
(ToJSON o, ToJSON p, ToJSON e, ToJSON (Output e)) => ToJSON (Diff o p e) Source # | |
Generic (Diff o p e) Source # | |
(Show o, Show p, Show e, Show (Output e)) => Show (Diff o p e) Source # | |
(Binary o, Binary p, Binary e, Binary (Output e)) => Binary (Diff o p e) Source # | |
(Eq o, Eq p, Eq e, Eq (Output e)) => Eq (Diff o p e) Source # | |
type Rep (Diff o p e) Source # | |
Defined in Data.CRDT.EventFold |