riak-1.0.0.1: A Haskell client for the Riak decentralized data store

Safe HaskellNone
LanguageHaskell98

Network.Riak.CRDT.Types

Contents

Description

Haskell-side view of CRDT

Synopsis

Types

data DataType Source

CRDT ADT.

get operations return value of this type

Counters

Modification

data CounterOp Source

Counters can be incremented/decremented

>>> CounterInc 1

Constructors

CounterInc !Count 

Sets

newtype Set Source

CRDT Set is a Data.Set

>>> Set (Data.Set.fromList ["foo","bar"])

Constructors

Set (Set ByteString) 

Modification

data SetOp Source

CRDT Set operations

Constructors

SetAdd ByteString

add element to the set

>>> SetAdd "foo"
SetRemove ByteString

remove element from the set

>>> SetRemove "bar"

Maps

newtype Map Source

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 

data MapField 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)

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 } } -- pseudo
Just (MapFlag (Flag False))

Modification

data MapOp Source

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

newtype MapPath Source

Selector (“xpath”) inside Map

Constructors

MapPath (NonEmpty ByteString) 

mapUpdate :: IsMapOp o => MapPath -> o -> MapOp infixr 5 Source

Registers

newtype Register Source

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 

Flags

newtype Flag Source

Flags can only be held as a Map element.

Flag can be set or unset

>>> Flag False

Constructors

Flag Bool 

Instances

Eq Flag Source 
Ord Flag Source 
Show Flag Source 
Generic Flag Source 
Monoid Flag Source

Last-wins monoid for Flag

NFData Flag Source 
Semigroup Flag Source

Last-wins semigroup for Flag

Default Flag Source 
type Rep Flag Source 

Modification

data FlagOp Source

Flags can be enabled / disabled

>>> FlagSet True

Constructors

FlagSet !Bool 

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