Skip to content

Commit

Permalink
ordered lists
Browse files Browse the repository at this point in the history
  • Loading branch information
0xtimmy committed Oct 15, 2023
1 parent 53c0396 commit 53e5fca
Show file tree
Hide file tree
Showing 2 changed files with 48 additions and 34 deletions.
9 changes: 7 additions & 2 deletions benchmarks/CRDTs/Clock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,16 @@ import Common
type Clock = Map Int
data Timestamp = Timestamp Int Clock

clk :: Timestamp -> Clock
clk t =
clock :: Timestamp -> Clock
clock t =
case t of
Timestamp _ c -> c

author :: Timestamp -> Int
author t =
case t of
Timestamp a _ -> a

init :: Int -> Clock
init uid = singleton uid 0

Expand Down
73 changes: 41 additions & 32 deletions benchmarks/CRDTs/IntOrderedList.hs
Original file line number Diff line number Diff line change
@@ -1,49 +1,58 @@
module IntOrderedList where
import Common
import Clock
--import List

data OrderedList a = OrderedList Clock (OrderedNode a)
data OrderedNode a = Bin Timestamp a Timestamp Timestamp (OrderedNode a)
| Tip

getStamp :: OrderedNode a -> Maybe Timestamp
getHead :: OrderedList a -> OrderedNode a
getHead list =
case list of
OrderedList _ node -> node

getClock :: OrderedList a -> Clock
getClock list =
case list of
OrderedList c _ -> c

getStamp :: OrderedNode a -> Common.Maybe Timestamp
getStamp x =
case x of
Bin t _ _ _ _ -> Just t
Tip -> Nothing

right :: OrderedNode a -> OrderedNode a
right x = case x of
Bin _ _ _ r _ -> r
Tip -> Tip
Bin t _ _ _ _ -> Common.Just t
Tip -> Common.Nothing

left :: OrderedNode a -> OrderedNode a
left x = case x of
Bin _ _ _ _ l -> l
next :: OrderedNode a -> OrderedNode a
next x = case x of
Bin _ _ _ _ n -> n
Tip -> Tip

singleton :: Int -> Int -> OrderedNode a
singleton :: Int -> a -> OrderedList a
singleton uid x =
let clk = singleton uid
in Bin clk x clk clk
let clk = Clock.init uid
t = (stamp uid clk)
in OrderedList clk (Bin t x t t Tip)

insert :: Int -> Int -> Timestamp -> Timestamp -> OrderedList
insert uid x clk l r node =
let t = step uid clk
int OrderedList t (place t uid x node l r)
insert :: Int -> a -> Timestamp -> Timestamp -> OrderedList a -> OrderedList a
insert uid x l r list =
let clk = step uid (getClock list)
in OrderedList clk (place uid (stamp uid clk) x (getHead list) l r)

place :: Timestamp -> Int -> Int -> OrderedNode a -> Timestamp -> Timestamp -> OrderedNode a
place clk uid x s l r =
place :: Int -> Timestamp -> a -> OrderedNode a -> Timestamp -> Timestamp -> OrderedNode a
place uid clk x s l r =
case (getStamp s) of
Nothing -> s
Just t -> case (compare t r) of
Eq -> s
Lt, Gt, Cc ->
let t v ls rs n
in Bin t v ls lr case (compare t l) of
Eq -> Bin (stamp uid clk) x l r (place uid clk x n l r)
Lt, Gt, Cc ->
if uid < t then place uid clk x n l r
else Bin (stamp uid clk) x l r (place uid clk x n l r)

value :: OrderedNode a -> List
Common.Nothing -> s
Common.Just t ->
case (Clock.compare (clock t) (clock r)) of
Eq -> s
_ -> case s of
Tip -> s
Bin t v ls rs n ->
case (Clock.compare (clock t) (clock l)) of
Eq -> Bin t v l r (Bin (stamp uid (Clock.clock clk)) x l r (place uid clk x n l r))
_ ->
if uid < (author t) then Bin t v l r (place uid clk x n l r)
else Bin t v l r (Bin (stamp uid (Clock.clock clk)) x l r (place uid clk x n l r))

--value :: OrderedNode a -> List a

0 comments on commit 53e5fca

Please sign in to comment.