{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.Legion.PowerState (
PowerState,
Event(..),
StateId,
DifferentOrigins(..),
new,
event,
merge,
mergeMaybe,
mergeEither,
acknowledge,
participate,
disassociate,
projectedValue,
infimumValue,
infimumParticipants,
allParticipants,
projParticipants,
divergent,
) where
import Prelude hiding (null)
import Control.Exception (throw, Exception)
import Data.Aeson (ToJSON, toJSON, object, (.=))
import Data.Binary (Binary(put, get))
import Data.Default.Class (Default(def))
import Data.DoubleWord (Word256(Word256), Word128(Word128))
import Data.Map (Map, filterWithKey, unionWith, minViewWithKey, keys,
toDescList, toAscList, fromAscList)
import Data.Set (Set, union, (\\), null, member)
import Data.Typeable (Typeable)
import Data.Word (Word64)
import GHC.Generics (Generic)
import qualified Data.Map as Map
import qualified Data.Set as Set
data PowerState o s p e r = PowerState {
origin :: o,
infimum :: Infimum s p,
events :: Map (StateId p) (Delta p e, Set p)
} deriving (Generic, Show, Eq)
instance (Binary o, Binary s, Binary p, Binary e) => Binary (PowerState o s p e r)
instance (Show o, Show s, Show p, Show e) => ToJSON (PowerState o s p e r) where
toJSON PowerState {origin, infimum, events} = object [
"origin" .= show origin,
"infimum" .= infimum,
"events" .= Map.fromList [
(show sid, (show e, Set.map show ps))
| (sid, (e, ps)) <- Map.toList events
]
]
data Infimum s p = Infimum {
stateId :: StateId p,
participants :: Set p,
stateValue :: s
} deriving (Generic, Show)
instance (Binary s, Binary p) => Binary (Infimum s p)
instance (Eq p) => Eq (Infimum s p) where
Infimum s1 _ _ == Infimum s2 _ _ = s1 == s2
instance (Ord p) => Ord (Infimum s p) where
compare (Infimum s1 _ _) (Infimum s2 _ _) = compare s1 s2
instance (Show s, Show p) => ToJSON (Infimum s p) where
toJSON Infimum {stateId, participants, stateValue} = object [
"stateId" .= show stateId,
"participants" .= Set.map show participants,
"stateValue" .= show stateValue
]
data StateId p
= BottomSid
| Sid Word256 p
deriving (Generic, Eq, Ord, Show)
instance (Binary p) => Binary (StateId p) where
put = put . toMaybe
where
toMaybe :: StateId p -> Maybe (Word64, Word64, Word64, Word64, p)
toMaybe BottomSid =
Nothing
toMaybe (Sid (Word256 (Word128 a b) (Word128 c d)) p) =
Just (a, b, c, d, p)
get = do
theThing <- get
return $ case theThing of
Nothing -> BottomSid
Just (a, b, c, d, p) -> Sid (Word256 (Word128 a b) (Word128 c d)) p
instance Default (StateId p) where
def = BottomSid
data DifferentOrigins o = DifferentOrigins o o deriving (Show, Typeable)
instance (Typeable o, Show o) => Exception (DifferentOrigins o)
data Delta p e
= Join p
| UnJoin p
| Event e
deriving (Generic, Show, Eq)
instance (Binary p, Binary e) => Binary (Delta p e)
class Event e o s | e -> s o where
apply :: e -> s -> (o, s)
new :: (Default s) => o -> Set p -> PowerState o s p e r
new origin participants =
PowerState {
origin,
infimum = Infimum {
stateId = def,
participants,
stateValue = def
},
events = Map.empty
}
merge :: (Eq o, Event e r s, Ord p, Show o, Typeable o)
=> PowerState o s p e r
-> PowerState o s p e r
-> (PowerState o s p e r, Map (StateId p) r)
merge a b = either throw id (mergeEither a b)
mergeMaybe :: (Eq o, Event e r s, Ord p)
=> PowerState o s p e r
-> PowerState o s p e r
-> Maybe (PowerState o s p e r, Map (StateId p) r)
mergeMaybe a b = either (const Nothing) Just (mergeEither a b)
mergeEither :: (Eq o, Event e r s, Ord p)
=> PowerState o s p e r
-> PowerState o s p e r
-> Either (DifferentOrigins o) (PowerState o s p e r, Map (StateId p) r)
mergeEither (PowerState o1 i1 d1) (PowerState o2 i2 d2) | o1 == o2 =
Right . reduce . removeRenegade $ PowerState {
origin = o1,
infimum,
events = removeObsolete (unionWith mergeAcks d1 d2)
}
where
infimum = max i1 i2
removeObsolete = filterWithKey (\k _ -> k > stateId infimum)
removeRenegade ps =
ps {
events =
fromAscList
. filter nonRenegade
. toAscList
. events
$ ps
}
where
nonRenegade (BottomSid, _) = True
nonRenegade (Sid _ p, _) = p `member` peers
peers = allParticipants ps
mergeAcks (e, s1) (_, s2) = (e, s1 `union` s2)
mergeEither PowerState {origin = o1} PowerState {origin = o2} =
Left (DifferentOrigins o1 o2)
acknowledge :: (Event e r s, Ord p)
=> p
-> PowerState o s p e r
-> (PowerState o s p e r, Map (StateId p) r)
acknowledge p ps@PowerState {events} =
reduce ps {events = fmap ackOne events}
where
ackOne (e, acks) = (e, Set.insert p acks)
participate :: (Ord p)
=> p
-> PowerState o s p e r
-> PowerState o s p e r
participate p ps@PowerState {events} = ps {
events = Map.insert (nextId p ps) (Join p, Set.empty) events
}
disassociate :: (Ord p)
=> p
-> PowerState o s p e r
-> PowerState o s p e r
disassociate p ps@PowerState {events} = ps {
events = Map.insert (nextId p ps) (UnJoin p, Set.empty) events
}
event :: (Ord p, Event e r s)
=> p
-> e
-> PowerState o s p e r
-> (r, PowerState o s p e r)
event p e ps@PowerState {events} = (
fst (apply e (projectedValue ps)),
ps {
events = Map.insert (nextId p ps) (Event e, Set.empty) events
}
)
projectedValue :: (Event e r s) => PowerState o s p e r -> s
projectedValue PowerState {infimum = Infimum {stateValue}, events} =
foldr (\ e s -> snd (apply e s)) stateValue changes
where
changes = foldr getDeltas [] (toDescList events)
getDeltas (_, (Event e, _)) acc = e:acc
getDeltas _ acc = acc
infimumValue :: PowerState o s p e r -> s
infimumValue PowerState {infimum = Infimum {stateValue}} = stateValue
infimumParticipants :: PowerState o s p e r -> Set p
infimumParticipants PowerState {infimum = Infimum {participants}} = participants
allParticipants :: (Ord p) => PowerState o s p e r -> Set p
allParticipants PowerState {
infimum = Infimum {participants},
events
} =
foldr updateParticipants participants (toDescList events)
where
updateParticipants (_, (Join p, _)) = Set.insert p
updateParticipants _ = id
projParticipants :: (Ord p) => PowerState o s p e r -> Set p
projParticipants PowerState {
infimum = Infimum {participants},
events
} =
foldr updateParticipants participants (toDescList events)
where
updateParticipants (_, (Join p, _)) = Set.insert p
updateParticipants (_, (UnJoin p, _)) = Set.delete p
updateParticipants _ = id
divergent :: (Ord p) => PowerState o s p e r -> Set p
divergent PowerState {
infimum = Infimum {participants},
events
} =
accum participants Set.empty (toAscList events)
where
accum _ d [] = d
accum j d ((_, (Join p, a)):moreDeltas) =
let
j2 = Set.insert p j
d2 = (j2 \\ a) `union` d
in
accum j2 d2 moreDeltas
accum j d ((_, (UnJoin p, a)):moreDeltas) =
let
j2 = Set.delete p j
d2 = (j \\ a) `union` d
in
accum j2 d2 moreDeltas
accum j d ((_, (Event _, a)):moreDeltas) =
let
d2 = (j \\ a) `union` d
in
accum j d2 moreDeltas
_divergences :: (Ord p) => PowerState o s p e r -> Map (StateId p) (e, Set p)
_divergences PowerState {events, infimum} =
go (participants infimum) (Map.toAscList events)
where
go :: (Ord p)
=> Set p
-> [(StateId p, (Delta p e, Set p))]
-> Map (StateId p) (e, Set p)
go _ [] = Map.empty
go ps ((sid, (Event e, p)):moreEvents) =
Map.insert sid (e, ps \\ p) (go ps moreEvents)
go ps ((_, (Join p, _)):moreEvents) = go (Set.insert p ps) moreEvents
go ps ((_, (UnJoin p, _)):moreEvents) = go (Set.delete p ps) moreEvents
reduce :: (Event e r s, Ord p)
=> PowerState o s p e r
-> (PowerState o s p e r, Map (StateId p) r)
reduce ps@PowerState {
infimum = infimum@Infimum {participants, stateValue},
events
} =
case minViewWithKey events of
Nothing -> (ps, Map.empty)
Just ((sid, (update, acks)), newDeltas) ->
if not . null $ participants \\ acks
then (ps, Map.empty)
else case update of
Join p -> reduce ps {
infimum = infimum {
stateId = sid,
participants = Set.insert p participants
},
events = newDeltas
}
UnJoin p -> reduce ps {
infimum = infimum {
stateId = sid,
participants = Set.delete p participants
},
events = newDeltas
}
Event e ->
let
(output, newState) = apply e stateValue
(ps2, outputs) = reduce ps {
infimum = infimum {
stateId = sid,
stateValue = newState
},
events = newDeltas
}
in (ps2, Map.insert sid output outputs)
nextId :: (Ord p) => p -> PowerState o s p e r -> StateId p
nextId p PowerState {infimum = Infimum {stateId}, events} =
case maximum (stateId:keys events) of
BottomSid -> Sid 0 p
Sid ord _ -> Sid (succ ord) p