| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Network.Riak.CRDT.Types
Contents
Description
Haskell-side view of CRDT
- data DataType
- newtype Counter = Counter Count
- type Count = Int64
- data CounterOp = CounterInc !Count
- newtype Set = Set (Set ByteString)
- data SetOp
- newtype Map = Map MapContent
- type MapContent = Map MapField MapEntry
- data MapField = MapField MapEntryTag ByteString
- data MapEntry
- = MapCounter !Counter
- | MapSet !Set
- | MapRegister !Register
- | MapFlag !Flag
- | MapMap !Map
- xlookup :: MapPath -> MapEntryTag -> Map -> Maybe MapEntry
- data MapOp
- newtype MapPath = MapPath (NonEmpty ByteString)
- data MapValueOp
- mapUpdate :: IsMapOp o => MapPath -> o -> MapOp
- (-/) :: ByteString -> MapPath -> MapPath
- newtype Register = Register ByteString
- data RegisterOp = RegisterSet !ByteString
- newtype Flag = Flag Bool
- data FlagOp = FlagSet !Bool
- data NonEmpty a :: * -> * = a :| [a]
- mapEntryTag :: MapValueOp -> MapEntryTag
- setFromSeq :: Seq ByteString -> Set
- data MapEntryTag
Types
CRDT ADT.
get operations return value of this type
Counters
CRDT Counter hold a integer Count
>>>Counter 42
Modification
Counters can be incremented/decremented
>>>CounterInc 1
Constructors
| CounterInc !Count |
Sets
CRDT Set is a Data.Set
>>>Set (Data.Set.fromList ["foo","bar"])
Constructors
| Set (Set ByteString) |
Modification
CRDT Set operations
Constructors
| SetAdd ByteString | add element to the set
|
| SetRemove ByteString | remove element from the set
|
Maps
CRDT Map is a Data.Map indexed by MapField and holding
MapEntry.
Maps are specials in a way that they can additionally
hold Flags, Registers, and most importantly, other Maps.
Constructors
| Map MapContent |
type MapContent = Map MapField MapEntry Source
CRDT Map is indexed by MapField, which is a name tagged by a type (there may be different entries with the same name, but different types)
Constructors
| MapField MapEntryTag ByteString |
CRDT Map holds values of type MapEntry
Constructors
| MapCounter !Counter | |
| MapSet !Set | |
| MapRegister !Register | |
| MapFlag !Flag | |
| MapMap !Map |
Inspection
xlookup :: MapPath -> MapEntryTag -> Map -> Maybe MapEntry Source
Lookup a value of a given MapEntryTag type on a given MapPath
inside a map
>>>lookup ("a" -/ "b") MapFlagTag $ { "a"/Map: { "b"/Flag: Flag False } } -- pseudoJust (MapFlag (Flag False))
Modification
map operations
It's easier to use mapUpdate:
>>>"x" -/ "y" -/ "z" `mapUpdate` SetAdd "elem"MapUpdate (MapPath ("x" :| ["y","z"])) (MapCounterOp (CounterInc 1))
Constructors
| MapRemove MapField | remove value in map |
| MapUpdate MapPath MapValueOp | update value on path by operation |
Selector (“xpath”) inside Map
Constructors
| MapPath (NonEmpty ByteString) |
data MapValueOp Source
Operations on map values
Constructors
| MapCounterOp !CounterOp | |
| MapSetOp !SetOp | |
| MapRegisterOp !RegisterOp | |
| MapFlagOp !FlagOp | |
| MapMapOp !MapOp |
Instances
(-/) :: ByteString -> MapPath -> MapPath infixr 6 Source
Registers
Registers can only be held as a Map element.
Register holds a ByteString.
Constructors
| Register ByteString |
Modification
data RegisterOp Source
Registers can be set to a value
>>>RegisterSet "foo"
Constructors
| RegisterSet !ByteString |
Instances
Flags
Modification
Flags can be enabled / disabled
>>>FlagSet True
Misc
data NonEmpty a :: * -> *
Constructors
| a :| [a] |
Instances
| Monad NonEmpty | |
| Functor NonEmpty | |
| MonadFix NonEmpty | |
| Applicative NonEmpty | |
| Foldable NonEmpty | |
| Traversable NonEmpty | |
| Generic1 NonEmpty | |
| MonadZip NonEmpty | |
| IsList (NonEmpty a) | |
| Eq a => Eq (NonEmpty a) | |
| Data a => Data (NonEmpty a) | |
| Ord a => Ord (NonEmpty a) | |
| Read a => Read (NonEmpty a) | |
| Show a => Show (NonEmpty a) | |
| Generic (NonEmpty a) | |
| NFData a => NFData (NonEmpty a) | |
| Hashable a => Hashable (NonEmpty a) | |
| Semigroup (NonEmpty a) | |
| type Rep1 NonEmpty = D1 D1NonEmpty (C1 C1_0NonEmpty ((:*:) (S1 NoSelector Par1) (S1 NoSelector (Rec1 [])))) | |
| type Rep (NonEmpty a) = D1 D1NonEmpty (C1 C1_0NonEmpty ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 [a])))) | |
| type Item (NonEmpty a) = a |
setFromSeq :: Seq ByteString -> Set Source
data MapEntryTag Source
Constructors
| MapCounterTag | |
| MapSetTag | |
| MapRegisterTag | |
| MapFlagTag | |
| MapMapTag |