Safe Haskell | None |
---|---|
Language | Haskell2010 |
RON.Data
Contents
Description
Typed and untyped RON tools
Synopsis
- class (Eq a, BoundedSemilattice a) => Reducible a where
- reducibleOpType :: UUID
- stateFromChunk :: [Op] -> a
- stateToChunk :: a -> [Op]
- applyPatches :: a -> Unapplied -> (a, Unapplied)
- reduceUnappliedPatches :: Unapplied -> Unapplied
- class Replicated a where
- encoding :: Encoding a
- class (Reducible (Rep a), Replicated a) => ReplicatedAsObject a where
- type Rep a
- newObject :: (ReplicaClock m, MonadState StateFrame m) => a -> m (ObjectRef a)
- readObject :: (MonadE m, MonadObjectState a m) => m a
- class Replicated a => ReplicatedAsPayload a where
- toPayload :: a -> Payload
- fromPayload :: MonadE m => Payload -> m a
- fromRon :: (MonadE m, Replicated a, MonadState StateFrame m) => Payload -> m a
- getObjectStateChunk :: forall a m. (MonadE m, MonadObjectState a m) => m (StateChunk (Rep a))
- newRon :: (Replicated a, ReplicaClock m, MonadState StateFrame m) => a -> m Payload
- objectEncoding :: ReplicatedAsObject a => Encoding a
- payloadEncoding :: ReplicatedAsPayload a => Encoding a
- rconcat :: forall a m. (MonadE m, MonadState StateFrame m, ReplicatedAsObject a) => NonEmpty UUID -> m a
- reduceObject :: MonadE m => ObjectFrame a -> ObjectFrame a -> m (ObjectFrame a)
- reduceStateFrame :: MonadE m => StateFrame -> StateFrame -> m StateFrame
- reduceWireFrame :: WireFrame -> WireFrame
- stateFromWireChunk :: forall a m. (MonadE m, Reducible a) => WireStateChunk -> m a
- stateToWireChunk :: forall rep. Reducible rep => rep -> WireStateChunk
- type ObjectStateT b m a = ReaderT (ObjectRef b) (StateT StateFrame m) a
- type MonadObjectState a m = (MonadReader (ObjectRef a) m, MonadState StateFrame m, Reducible (Rep a))
- evalObjectState :: Monad m => ObjectFrame b -> ObjectStateT b m a -> m a
- evalObjectState_ :: Monad m => StateT StateFrame m a -> m a
- execObjectState :: Monad m => ObjectFrame b -> ObjectStateT b m a -> m (ObjectFrame b)
- execObjectState_ :: Monad m => StateT StateFrame m a -> m StateFrame
- newObjectFrame :: (ReplicatedAsObject a, ReplicaClock m) => a -> m (ObjectFrame a)
- newObjectFrameWith :: Functor m => StateT StateFrame m (ObjectRef a) -> m (ObjectFrame a)
- runObjectState :: Functor m => ObjectFrame b -> ObjectStateT b m a -> m (a, ObjectFrame b)
- runObjectState_ :: StateT StateFrame m a -> m (a, StateFrame)
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
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
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 # | |
Defined in RON.Data.Internal | |
Replicated Char Source # | |
Defined in RON.Data.Internal | |
Replicated Int64 Source # | |
Defined in RON.Data.Internal | |
Replicated Text Source # | |
Defined in RON.Data.Internal | |
Replicated UUID Source # | |
Defined in RON.Data.Internal | |
Replicated Day Source # | |
Defined in RON.Data.Time | |
Replicated VersionVector Source # | |
Defined in RON.Data.VersionVector Methods encoding :: Encoding VersionVector Source # | |
Replicated (ObjectRef a) Source # | |
Defined in RON.Data.Internal | |
Replicated a => Replicated (ORSet a) Source # | |
Defined in RON.Data.ORSet | |
Replicated a => Replicated (RGA a) Source # | |
Defined in RON.Data.RGA |
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
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 # | |
Defined in RON.Data.VersionVector Associated Types type Rep VersionVector :: Type Source # Methods newObject :: (ReplicaClock m, MonadState StateFrame m) => VersionVector -> m (ObjectRef VersionVector) Source # readObject :: (MonadE m, MonadObjectState VersionVector m) => m VersionVector Source # | |
Replicated a => ReplicatedAsObject (ORSet a) Source # | |
Defined in RON.Data.ORSet Methods newObject :: (ReplicaClock m, MonadState StateFrame m) => ORSet a -> m (ObjectRef (ORSet a)) Source # readObject :: (MonadE m, MonadObjectState (ORSet a) m) => m (ORSet a) Source # | |
Replicated a => ReplicatedAsObject (RGA a) Source # | |
Defined in RON.Data.RGA Methods newObject :: (ReplicaClock m, MonadState StateFrame m) => RGA a -> m (ObjectRef (RGA a)) Source # readObject :: (MonadE m, MonadObjectState (RGA a) m) => m (RGA a) 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.
rconcat :: forall a m. (MonadE m, MonadState StateFrame m, ReplicatedAsObject a) => NonEmpty UUID -> m a Source #
reduceObject :: MonadE m => ObjectFrame a -> ObjectFrame a -> m (ObjectFrame a) Source #
Reduce object with frame from another version of the same object.
reduceStateFrame :: MonadE m => StateFrame -> StateFrame -> m StateFrame Source #
reduceWireFrame :: WireFrame -> WireFrame Source #
stateFromWireChunk :: forall a m. (MonadE m, Reducible a) => WireStateChunk -> m a Source #
stateToWireChunk :: forall rep. Reducible rep => rep -> WireStateChunk Source #
Object-state monad
type ObjectStateT b m a = ReaderT (ObjectRef b) (StateT StateFrame m) a Source #
type MonadObjectState a m = (MonadReader (ObjectRef a) m, MonadState StateFrame m, Reducible (Rep a)) Source #
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