ron-rdt-0.10: Replicated Data Types (RON-RDT)

Safe HaskellNone
LanguageHaskell2010

RON.Data

Contents

Description

Typed and untyped RON tools

Synopsis

Documentation

class (Eq a, BoundedSemilattice a) => Reducible a where Source #

Untyped-reducible types. Untyped means if this type is a container then the types of data contained in it is not considered.

Minimal complete definition

reducibleOpType, stateFromChunk, stateToChunk

Methods

reducibleOpType :: UUID Source #

UUID of the type

stateFromChunk :: [Op] -> a Source #

Load a state from a state chunk.

stateToChunk :: a -> [Op] Source #

Store a state to a state chunk

applyPatches :: a -> Unapplied -> (a, Unapplied) Source #

Merge a state with patches and raw ops

reduceUnappliedPatches :: Unapplied -> Unapplied Source #

Merge patches and raw ops into bigger patches or throw obsolete ops

Instances
Reducible LwwRep Source # 
Instance details

Defined in RON.Data.LWW

Methods

reducibleOpType :: UUID Source #

stateFromChunk :: [Op] -> LwwRep Source #

stateToChunk :: LwwRep -> [Op] Source #

applyPatches :: LwwRep -> Unapplied -> (LwwRep, Unapplied) Source #

reduceUnappliedPatches :: Unapplied -> Unapplied Source #

Reducible ORSetRep Source # 
Instance details

Defined in RON.Data.ORSet

Methods

reducibleOpType :: UUID Source #

stateFromChunk :: [Op] -> ORSetRep Source #

stateToChunk :: ORSetRep -> [Op] Source #

applyPatches :: ORSetRep -> Unapplied -> (ORSetRep, Unapplied) Source #

reduceUnappliedPatches :: Unapplied -> Unapplied Source #

Reducible RgaRep Source # 
Instance details

Defined in RON.Data.RGA

Methods

reducibleOpType :: UUID Source #

stateFromChunk :: [Op] -> RgaRep Source #

stateToChunk :: RgaRep -> [Op] Source #

applyPatches :: RgaRep -> Unapplied -> (RgaRep, Unapplied) Source #

reduceUnappliedPatches :: Unapplied -> Unapplied Source #

Reducible VersionVector Source # 
Instance details

Defined in RON.Data.VersionVector

class Replicated a where Source #

Base class for typed encoding

Methods

encoding :: Encoding a Source #

Instances SHOULD implement encoding either as objectEncoding or as payloadEncoding

Instances
Replicated Bool Source # 
Instance details

Defined in RON.Data.Internal

Methods

encoding :: Encoding Bool Source #

Replicated Char Source # 
Instance details

Defined in RON.Data.Internal

Methods

encoding :: Encoding Char Source #

Replicated Int64 Source # 
Instance details

Defined in RON.Data.Internal

Methods

encoding :: Encoding Int64 Source #

Replicated Text Source # 
Instance details

Defined in RON.Data.Internal

Methods

encoding :: Encoding Text Source #

Replicated UUID Source # 
Instance details

Defined in RON.Data.Internal

Methods

encoding :: Encoding UUID Source #

Replicated Day Source # 
Instance details

Defined in RON.Data.Time

Methods

encoding :: Encoding Day Source #

Replicated VersionVector Source # 
Instance details

Defined in RON.Data.VersionVector

Methods

encoding :: Encoding VersionVector Source #

Replicated (ObjectRef a) Source # 
Instance details

Defined in RON.Data.Internal

Methods

encoding :: Encoding (ObjectRef a) Source #

Replicated a => Replicated (ORSet a) Source # 
Instance details

Defined in RON.Data.ORSet

Methods

encoding :: Encoding (ORSet a) Source #

Replicated a => Replicated (RGA a) Source # 
Instance details

Defined in RON.Data.RGA

Methods

encoding :: Encoding (RGA a) Source #

class (Reducible (Rep a), Replicated a) => ReplicatedAsObject a where Source #

Instances of this class are encoded as objects. An enclosing object's payload will be filled with this object's id.

Law: encoding == objectEncoding

Associated Types

type Rep a Source #

Untyped RON-RDT representation

Methods

newObject :: (ReplicaClock m, MonadState StateFrame m) => a -> m (ObjectRef a) Source #

Encode data. Write frame and return id.

readObject :: (MonadE m, MonadObjectState a m) => m a Source #

Decode data

Instances
ReplicatedAsObject VersionVector Source # 
Instance details

Defined in RON.Data.VersionVector

Associated Types

type Rep VersionVector :: Type Source #

Replicated a => ReplicatedAsObject (ORSet a) Source # 
Instance details

Defined in RON.Data.ORSet

Associated Types

type Rep (ORSet a) :: Type Source #

Replicated a => ReplicatedAsObject (RGA a) Source # 
Instance details

Defined in RON.Data.RGA

Associated Types

type Rep (RGA a) :: Type Source #

class Replicated a => ReplicatedAsPayload a where Source #

Instances of this class are encoded as payload only.

Law: encoding == payloadEncoding

Methods

toPayload :: a -> Payload Source #

Encode data

fromPayload :: MonadE m => Payload -> m a Source #

Decode data

fromRon :: (MonadE m, Replicated a, MonadState StateFrame m) => Payload -> m a Source #

Decode typed data from a payload. The implementation may use other objects in the frame to resolve references.

getObjectStateChunk :: forall a m. (MonadE m, MonadObjectState a m) => m (StateChunk (Rep a)) Source #

newRon :: (Replicated a, ReplicaClock m, MonadState StateFrame m) => a -> m Payload Source #

Encode typed data to a payload with possible addition objects

objectEncoding :: ReplicatedAsObject a => Encoding a Source #

Standard implementation of Replicated for ReplicatedAsObject types.

payloadEncoding :: ReplicatedAsPayload a => Encoding a Source #

Standard implementation of Replicated for ReplicatedAsPayload types.

reduceObject :: MonadE m => ObjectFrame a -> ObjectFrame a -> m (ObjectFrame a) Source #

Reduce object with frame from another version of the same object.

stateFromWireChunk :: forall a m. (MonadE m, Reducible a) => WireStateChunk -> m a Source #

stateToWireChunk :: forall rep. Reducible rep => rep -> WireStateChunk Source #

Object-state monad

evalObjectState :: Monad m => ObjectFrame b -> ObjectStateT b m a -> m a Source #

Run ObjectFrame action

evalObjectState_ :: Monad m => StateT StateFrame m a -> m a Source #

Run ObjectFrame action, starting with an empty frame

execObjectState :: Monad m => ObjectFrame b -> ObjectStateT b m a -> m (ObjectFrame b) Source #

Run ObjectFrame action

execObjectState_ :: Monad m => StateT StateFrame m a -> m StateFrame Source #

Run ObjectFrame action, starting with an empty frame

newObjectFrame :: (ReplicatedAsObject a, ReplicaClock m) => a -> m (ObjectFrame a) Source #

Create new ObjectFrame from a value

newObjectFrameWith :: Functor m => StateT StateFrame m (ObjectRef a) -> m (ObjectFrame a) Source #

Create new ObjectFrame with an action

runObjectState :: Functor m => ObjectFrame b -> ObjectStateT b m a -> m (a, ObjectFrame b) Source #

Run ObjectFrame action

runObjectState_ :: StateT StateFrame m a -> m (a, StateFrame) Source #

Run ObjectFrame action, starting with an empty frame