crdt-2.0: Conflict-free replicated data types

Safe HaskellSafe
LanguageHaskell2010

CRDT.Cm

Synopsis

Documentation

class CausalOrd a where Source #

Partial order for causal semantics. Values of some type may be ordered and causally-ordered different ways.

Minimal complete definition

before

Methods

before :: a -> a -> Bool Source #

Instances

CausalOrd (Counter a) Source #

Empty order, allowing arbitrary reordering

Methods

before :: Counter a -> Counter a -> Bool Source #

Eq a => CausalOrd (GSet a) Source # 

Methods

before :: GSet a -> GSet a -> Bool Source #

Eq a => CausalOrd (TPSet a) Source # 

Methods

before :: TPSet a -> TPSet a -> Bool Source #

CausalOrd (LWW a) Source # 

Methods

before :: LWW a -> LWW a -> Bool Source #

class (CausalOrd u, Eq (View u)) => CmRDT u where Source #

Operation-based, or commutative (Cm) replicated data type.

Implementation

In Haskell, a CmRDT implementation consists of 3 types — a payload, an operation (op) and an update.

Payload
Internal state of a replica.
Operation
User's request to update.
Update
Operation to be applied to other replicas.

For many types operation and update may be the same. But for LWW, for instance, this rule doesn't hold: user can request only value, and type attaches a timestamp to it.

Additional constraint — commutativity law

Concurrent updates are observed equally.

∀ up1 up2 s .
concurrent up1 up2 ==>
    observe (updateDownstream up1 . updateDownstream up2 $ s) ==
    observe (updateDownstream up2 . updateDownstream up1 $ s)

Idempotency doesn't need to hold.

Minimal complete definition

updateDownstream

Associated Types

type Op u Source #

type Payload u Source #

type View u Source #

Methods

updateAtSourcePre :: Op u -> Payload u -> Bool Source #

Precondition for updateAtSource. Calculates if the operation is applicable to the current state.

updateAtSource :: Clock m => Op u -> m u Source #

Generate an update to the local and remote replicas. Doesn't have sense if updateAtSourcePre is false.

May or may not use clock.

updateAtSource :: (Clock m, Op u ~ u) => Op u -> m u Source #

Generate an update to the local and remote replicas. Doesn't have sense if updateAtSourcePre is false.

May or may not use clock.

updateDownstream :: u -> Payload u -> Payload u Source #

Apply an update to the payload. An invalid update must be ignored.

view :: Payload u -> View u Source #

Extract user-visible value from payload

view :: Payload u ~ View u => Payload u -> View u Source #

Extract user-visible value from payload

Instances

(Num a, Eq a) => CmRDT (Counter a) Source # 

Associated Types

type Op (Counter a) :: * Source #

type Payload (Counter a) :: * Source #

type View (Counter a) :: * Source #

Ord a => CmRDT (GSet a) Source # 

Associated Types

type Op (GSet a) :: * Source #

type Payload (GSet a) :: * Source #

type View (GSet a) :: * Source #

Ord a => CmRDT (TPSet a) Source # 

Associated Types

type Op (TPSet a) :: * Source #

type Payload (TPSet a) :: * Source #

type View (TPSet a) :: * Source #

Eq a => CmRDT (LWW a) Source # 

Associated Types

type Op (LWW a) :: * Source #

type Payload (LWW a) :: * Source #

type View (LWW a) :: * Source #

Methods

updateAtSourcePre :: Op (LWW a) -> Payload (LWW a) -> Bool Source #

updateAtSource :: Clock m => Op (LWW a) -> m (LWW a) Source #

updateDownstream :: LWW a -> Payload (LWW a) -> Payload (LWW a) Source #

view :: Payload (LWW a) -> View (LWW a) Source #

concurrent :: CausalOrd a => a -> a -> Bool Source #

Not comparable, i. e. ¬(a ≤ b) ∧ ¬(b ≤ a).