crdt-10.2: Conflict-free replicated data types

Safe HaskellNone
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

precedes

Methods

precedes :: a -> a -> Bool Source #

x precedes y means that x must go before y and y can not go before x.

Instances

CausalOrd (LWW a) Source # 

Methods

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

Eq a => CausalOrd (TwoPSet a) Source # 

Methods

precedes :: TwoPSet a -> TwoPSet a -> Bool Source #

CausalOrd (RGA a) Source # 

Methods

precedes :: RGA a -> RGA a -> Bool Source #

CausalOrd (ORSet a) Source # 

Methods

precedes :: ORSet a -> ORSet a -> Bool Source #

CausalOrd (GSet a) Source # 

Methods

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

CausalOrd (Counter a) Source #

Empty order, allowing arbitrary reordering

Methods

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

class (CausalOrd op, Eq (Payload op)) => CmRDT op 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 intent.

Payload
Internal state of a replica.
Intent
User's request to update.
Operation (Op)
Operation to be applied to other replicas.

For many types operation and intent 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.

∀ op1 op2 .
concurrent op1 op2 ==> apply op1 . apply op2 == apply op2 . apply op1

Idempotency doesn't need to hold.

Minimal complete definition

initial, apply

Associated Types

type Intent op Source #

type Payload op Source #

Methods

initial :: Payload op Source #

makeOp :: Clock m => Intent op -> Payload op -> Maybe (m op) Source #

Generate an update to the local and remote replicas.

Returns Nothing if the intended operation is not applicable.

makeOp :: (Intent op ~ op, Applicative m) => Intent op -> Payload op -> Maybe (m op) Source #

Generate an update to the local and remote replicas.

Returns Nothing if the intended operation is not applicable.

apply :: op -> Payload op -> Payload op Source #

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

TODO(Syrovetsky, 2017-12-05) There is no downstream precondition yet. We must make a test for it first.

Instances

Eq a => CmRDT (LWW a) Source # 

Associated Types

type Intent (LWW a) :: * Source #

type Payload (LWW a) :: * Source #

Methods

initial :: Payload (LWW a) Source #

makeOp :: Clock m => Intent (LWW a) -> Payload (LWW a) -> Maybe (m (LWW a)) Source #

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

Ord a => CmRDT (TwoPSet a) Source # 

Associated Types

type Intent (TwoPSet a) :: * Source #

type Payload (TwoPSet a) :: * Source #

(AsEmpty a, Ord a) => CmRDT (RGA a) Source # 

Associated Types

type Intent (RGA a) :: * Source #

type Payload (RGA a) :: * Source #

Methods

initial :: Payload (RGA a) Source #

makeOp :: Clock m => Intent (RGA a) -> Payload (RGA a) -> Maybe (m (RGA a)) Source #

apply :: RGA a -> Payload (RGA a) -> Payload (RGA a) Source #

Ord a => CmRDT (ORSet a) Source # 

Associated Types

type Intent (ORSet a) :: * Source #

type Payload (ORSet a) :: * Source #

Methods

initial :: Payload (ORSet a) Source #

makeOp :: Clock m => Intent (ORSet a) -> Payload (ORSet a) -> Maybe (m (ORSet a)) Source #

apply :: ORSet a -> Payload (ORSet a) -> Payload (ORSet a) Source #

Ord a => CmRDT (GSet a) Source # 

Associated Types

type Intent (GSet a) :: * Source #

type Payload (GSet a) :: * Source #

Methods

initial :: Payload (GSet a) Source #

makeOp :: Clock m => Intent (GSet a) -> Payload (GSet a) -> Maybe (m (GSet a)) Source #

apply :: GSet a -> Payload (GSet a) -> Payload (GSet a) Source #

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

Associated Types

type Intent (Counter a) :: * Source #

type Payload (Counter a) :: * Source #

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

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

query :: forall op f. (CmRDT op, Foldable f) => f op -> Payload op Source #

makeAndApplyOp :: (CmRDT op, Clock m, MonadFail m, MonadState (Payload op) m) => Intent op -> m op Source #

Make op and apply it to the payload -- a common routine at the source node.

makeAndApplyOps :: (CmRDT op, Clock m, MonadFail m, MonadState (Payload op) m, Traversable f) => f (Intent op) -> m (f op) Source #