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

Safe HaskellNone
LanguageHaskell2010

RON.Data.ORSet

Contents

Description

Observed-Remove Set (OR-Set)

Synopsis

Documentation

newtype ORSet a Source #

Type-directing wrapper for typed OR-Set. Eq instance is purely technical, it doesn't use Ord, nor Hashable, so its result may be confusing.

Constructors

ORSet [a] 
Instances
Eq a => Eq (ORSet a) Source # 
Instance details

Defined in RON.Data.ORSet

Methods

(==) :: ORSet a -> ORSet a -> Bool #

(/=) :: ORSet a -> ORSet a -> Bool #

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

Defined in RON.Data.ORSet

Methods

showsPrec :: Int -> ORSet a -> ShowS #

show :: ORSet a -> String #

showList :: [ORSet a] -> ShowS #

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

Defined in RON.Data.ORSet

Associated Types

type Rep (ORSet a) :: Type Source #

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

Defined in RON.Data.ORSet

Methods

encoding :: Encoding (ORSet a) Source #

type Rep (ORSet a) Source # 
Instance details

Defined in RON.Data.ORSet

type Rep (ORSet a) = ORSetRep

newtype ORSetItem a Source #

Reference to an item inside an ORSet.

Constructors

ORSetItem UUID 
Instances
Show (ORSetItem a) Source # 
Instance details

Defined in RON.Data.ORSet

type ORSetMap k v = ORSet (k, v) Source #

data ORSetRep Source #

Untyped OR-Set. Implementation: a map from the itemKey to the original op. Each time a value is added, a new item=op is created. Deletion of a value replaces all its known items with tombstone ops.

Instances
Eq ORSetRep Source # 
Instance details

Defined in RON.Data.ORSet

Show ORSetRep Source # 
Instance details

Defined in RON.Data.ORSet

Semigroup ORSetRep Source # 
Instance details

Defined in RON.Data.ORSet

Monoid ORSetRep Source # 
Instance details

Defined in RON.Data.ORSet

Semilattice ORSetRep Source #

Laws: 1. Idempotent because unionWith is idempotent. 2. Commutative because preferTombstone is commutative.

Instance details

Defined in RON.Data.ORSet

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 #

addValue :: (Replicated a, ReplicaClock m, MonadE m, MonadObjectState (ORSet a) m) => a -> m () Source #

Encode a value and add a it to the OR-Set

findAnyAlive :: (MonadE m, MonadObjectState (ORSet item) m) => m (Maybe (ORSetItem item)) Source #

Find any alive item. If no alive item found, return Nothing.

findAnyAlive' :: (MonadE m, MonadObjectState (ORSet item) m) => m (ORSetItem item) Source #

Find any alive item. If no alive item found, report an error.

removeRef :: (MonadE m, ReplicaClock m, MonadObjectState (ORSet a) m) => Object a -> m () Source #

Remove an object reference from the OR-Set

removeValue :: (ReplicatedAsPayload a, MonadE m, ReplicaClock m, MonadObjectState (ORSet a) m) => a -> m () Source #

Remove an atomic value from the OR-Set

zoomItem :: MonadE m => ORSetItem item -> ObjectStateT item m a -> ObjectStateT (ORSet item) m a Source #

Go from modification of the whole set to the modification of an item object.

struct_set

assignField Source #

Arguments

:: (Replicated a, ReplicaClock m, MonadE m, MonadObjectState struct m) 
=> UUID

Field name

-> Maybe a

Value

-> m () 

Assign a value to a field

newStruct :: (MonadState StateFrame m, ReplicaClock m) => [(UUID, Maybe (Instance Replicated))] -> m UUID Source #

Create an ORSet object from a list of named fields.

viewField Source #

Arguments

:: (MonadE m, MonadState StateFrame m, ReplicatedAsObject a) 
=> UUID

Field name

-> StateChunk ORSetRep

ORSet object chunk

-> m (Maybe a) 

Decode field value, merge all versions, return Nothing if no versions

viewFieldLWW Source #

Arguments

:: (MonadE m, MonadState StateFrame m, Replicated a) 
=> UUID

Field name

-> StateChunk ORSetRep

ORSet object chunk

-> m (Maybe a) 

Decode field value, keep last version only

viewFieldMax Source #

Arguments

:: (MonadE m, Ord a, ReplicatedAsPayload a) 
=> UUID

Field name

-> StateChunk ORSetRep

ORSet object chunk

-> m (Maybe a) 

Decode field value, keep max value only, only for Integer and Float

viewFieldMin Source #

Arguments

:: (MonadE m, Ord a, ReplicatedAsPayload a) 
=> UUID

Field name

-> StateChunk ORSetRep

ORSet object chunk

-> m (Maybe a) 

Decode field value, keep min value only, only for Integer and Float

viewFieldSet Source #

Arguments

:: (MonadE m, MonadState StateFrame m, Replicated a) 
=> UUID

Field name

-> StateChunk ORSetRep

ORSet object chunk

-> m [a] 

Decode field value, keep all versions

zoomFieldObject Source #

Arguments

:: (MonadE m, ReplicaClock m, ReplicatedAsObject field, ReplicatedAsObject struct) 
=> UUID

Field name

-> ObjectStateT field m a

Inner object modifier

-> ObjectStateT struct m a 

Pseudo-lens to an object inside a specified field