{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
module Network.Riak.CRDT.Types (
DataType(..)
, Counter(..), Count
, CounterOp(..)
, Set(..)
, SetOp(..)
, Map(..), MapContent
, MapField(..)
, MapEntry(..)
, xlookup
, MapOp(..), MapPath(..), MapValueOp(..), mapUpdate, (-/)
, Register(..)
, RegisterOp(..)
, Flag(..)
, FlagOp(..)
, NonEmpty(..), mapEntryTag, setFromSeq, MapEntryTag(..)
) where
import Control.DeepSeq (NFData)
import Data.ByteString.Lazy (ByteString)
import Data.Default.Class
import qualified Data.Foldable as F
import Data.Int (Int64)
import Data.List.NonEmpty
import qualified Data.Map.Strict as M
import Data.Semigroup
import qualified Data.Sequence as Seq
import qualified Data.Set as S
import Data.String (IsString(..))
import GHC.Generics (Generic)
data MapField = MapField MapEntryTag ByteString deriving (Eq,Ord,Show,Generic)
instance NFData MapField
newtype Map = Map MapContent deriving (Eq,Show,Generic)
instance NFData Map
type MapContent = M.Map MapField MapEntry
instance Default Map where
def = Map M.empty
data MapEntryTag = MapCounterTag
| MapSetTag
| MapRegisterTag
| MapFlagTag
| MapMapTag
deriving (Eq,Ord,Show,Generic)
instance NFData MapEntryTag
data MapEntry = MapCounter !Counter
| MapSet !Set
| MapRegister !Register
| MapFlag !Flag
| MapMap !Map
deriving (Eq,Show,Generic)
instance NFData MapEntry
mapEntryTag :: MapValueOp -> MapEntryTag
mapEntryTag MapCounterOp{} = MapCounterTag
mapEntryTag MapSetOp{} = MapSetTag
mapEntryTag MapRegisterOp{} = MapRegisterTag
mapEntryTag MapFlagOp{} = MapFlagTag
mapEntryTag MapMapOp{} = MapMapTag
newtype MapPath = MapPath (NonEmpty ByteString) deriving (Eq,Show)
data MapOp = MapRemove MapField
| MapUpdate MapPath MapValueOp
deriving (Eq,Show)
data MapOp_ op = MapRemove_ MapField
| MapUpdate_ MapPath op
deriving Show
instance IsString MapPath where
fromString s = MapPath (fromString s :| [])
(-/) :: ByteString -> MapPath -> MapPath
e -/ (MapPath p) = MapPath (e <| p)
infixr 6 -/
class IsMapOp op where toValueOp :: op -> MapValueOp
instance IsMapOp CounterOp where toValueOp = MapCounterOp
instance IsMapOp FlagOp where toValueOp = MapFlagOp
instance IsMapOp RegisterOp where toValueOp = MapRegisterOp
instance IsMapOp SetOp where toValueOp = MapSetOp
mapUpdate :: IsMapOp o => MapPath -> o -> MapOp
p `mapUpdate` op = MapUpdate p (toValueOp op)
infixr 5 `mapUpdate`
xlookup :: MapPath -> MapEntryTag -> Map -> Maybe MapEntry
xlookup (MapPath (e :| [])) tag (Map m) = M.lookup (MapField tag e) m
xlookup (MapPath (e :| (r:rs))) tag (Map m)
| Just (MapMap m') <- inner = xlookup (MapPath (r :| rs)) tag m'
| otherwise = Nothing
where inner = M.lookup (MapField MapMapTag e) m
data RegisterOp = RegisterSet !ByteString deriving (Eq,Show)
data FlagOp = FlagSet !Bool deriving (Eq,Show)
newtype Flag = Flag Bool deriving (Eq,Ord,Show,Generic)
instance NFData Flag
instance Monoid Flag where
mempty = Flag False
mappend = (<>)
instance Semigroup Flag where
a <> b = getLast (Last a <> Last b)
instance Default Flag where
def = mempty
newtype Register = Register ByteString deriving (Eq,Show,Generic)
instance NFData Register
instance Monoid Register where
mempty = Register ""
mappend = (<>)
instance Semigroup Register where
a <> b = getLast (Last a <> Last b)
instance Default Register where
def = mempty
data MapValueOp = MapCounterOp !CounterOp
| MapSetOp !SetOp
| MapRegisterOp !RegisterOp
| MapFlagOp !FlagOp
| MapMapOp !MapOp
deriving (Eq,Show)
data DataType = DTCounter Counter
| DTSet Set
| DTMap Map
deriving (Eq,Show,Generic)
instance NFData DataType
newtype Set = Set (S.Set ByteString) deriving (Eq,Ord,Show,Generic,Monoid)
instance NFData Set
instance Semigroup Set where
Set a <> Set b = Set (a <> b)
instance Default Set where
def = Set mempty
data SetOp = SetAdd ByteString
| SetRemove ByteString
deriving (Eq,Show)
setFromSeq :: Seq.Seq ByteString -> Set
setFromSeq = Set . S.fromList . F.toList
newtype Counter = Counter Count deriving (Eq,Ord,Num,Show,Generic)
type Count = Int64
instance NFData Counter
instance Semigroup Counter where
Counter a <> Counter b = Counter . getSum $ Sum a <> Sum b
instance Monoid Counter where
mempty = Counter 0
mappend = (<>)
instance Default Counter where
def = mempty
data CounterOp = CounterInc !Count deriving (Eq,Show)
instance Semigroup CounterOp where
CounterInc x <> CounterInc y = CounterInc . getSum $ Sum x <> Sum y
instance Monoid CounterOp where
mempty = CounterInc 0
CounterInc x `mappend` CounterInc y = CounterInc . getSum $ Sum x <> Sum y