Safe Haskell | Safe |
---|---|
Language | Haskell98 |
A vector clock implementation in terms of simply-linked lists.
- data VectorClock a b
- empty :: VectorClock a b
- singleton :: Ord a => a -> b -> VectorClock a b
- fromList :: Ord a => [(a, b)] -> VectorClock a b
- null :: VectorClock a b -> Bool
- size :: VectorClock a b -> Int
- member :: Ord a => a -> VectorClock a b -> Bool
- lookup :: Ord a => a -> VectorClock a b -> Maybe b
- toList :: VectorClock a b -> [(a, b)]
- insert :: Ord a => a -> b -> VectorClock a b -> VectorClock a b
- inc :: (Ord a, Num b) => a -> VectorClock a b -> Maybe (VectorClock a b)
- incWithDefault :: (Ord a, Num b) => a -> VectorClock a b -> b -> VectorClock a b
- delete :: Ord a => a -> VectorClock a b -> VectorClock a b
- combine :: (Ord a, Ord b) => (a -> Maybe b -> Maybe b -> Maybe b) -> VectorClock a b -> VectorClock a b -> VectorClock a b
- max :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> VectorClock a b
- diff :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> Maybe (VectorClock a b)
- data Relation
- = Causes
- | CausedBy
- | Concurrent
- relation :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> Relation
- causes :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> Bool
- valid :: (Ord a, Ord b) => VectorClock a b -> Bool
Usage example
To create a vector clock, start from empty
and insert
elements
into it. As a shortcut, fromList
just inserts all the elements
in a list, in order.
let vc = empty in let vc' = insert 'a' 1 vc in let vc'' = insert 'b' 2 vc in vc'' == fromList [('a', 1), ('b', 2)]
Note that, for different keys, the order of insertion does not matter:
fromList [('a', 1), ('b', 2)] == fromList [('b', 2), ('a', 1)]
Once you have a given vector clock, you can lookup
its fields,
check that keys are member
s, or convert it back toList
form.
lookup 'a' [('a', 1), ('b', 2)] == Just 1 lookup 'c' [('a', 1), ('b', 2)] == Nothing
The main operations that you would do with a vector clcok are to
inc
crement the entry corresponding to the current process and to
update the process's vector clock with the max
of its and the
received message's clocks.
inc 'a' [('a', 1), ('b', 2)] = Just [('a', 2), ('b', 2)] max [('a', 1), ('b', 2)] [('c', 3), ('b', 1)] == [('a', 1), ('b', 2), ('c' 3)]
Finally, upon receiving different messages, you may wish to
discover the relation
ship, if any, between them. This
information could be useful in determining the correct order to
process the messages.
relation (fromList [('a', 1), ('b', 2)]) (fromList [('a', 2), ('b', 2)]) == Causes relation (fromList [('a', 2), ('b', 2)]) (fromList [('a', 1), ('b', 2)]) == CausedBy relation (fromList [('a', 2), ('b', 2)]) (fromList [('a', 1), ('b', 3)]) == Concurrent
In order to send and receive vector clocks, they must first be
serialized. For this purpose, there is a Binary
instance for
VectorClock
. Additionally, there are Data
, Typeable
, and
Generic
instances, which allow packages such as cereal
, and
sexp
to automatically generate serializers and deserializers.
Vector clock type
data VectorClock a b Source #
A vector clock is, conceptually, an associtive list sorted by the value of the key, where each key appears only once.
Functor (VectorClock a) Source # | |
Foldable (VectorClock a) Source # | |
Traversable (VectorClock a) Source # | |
(Eq a, Eq b) => Eq (VectorClock a b) Source # | |
(Data a, Data b) => Data (VectorClock a b) Source # | |
(Show a, Show b) => Show (VectorClock a b) Source # | |
Generic (VectorClock a b) Source # | |
(Binary a, Binary b) => Binary (VectorClock a b) Source # | |
type Rep (VectorClock a b) Source # | |
Construction
empty :: VectorClock a b Source #
O(1). The empty vector clock.
singleton :: Ord a => a -> b -> VectorClock a b Source #
O(1). A vector clock with a single element.
fromList :: Ord a => [(a, b)] -> VectorClock a b Source #
O(N). Insert each entry in the list one at a time.
Query
null :: VectorClock a b -> Bool Source #
O(1). Is the vector clock empty?
size :: VectorClock a b -> Int Source #
O(N). The number of entries in the vector clock.
member :: Ord a => a -> VectorClock a b -> Bool Source #
O(N). Is the given key a key in an entry of the vector clock?
lookup :: Ord a => a -> VectorClock a b -> Maybe b Source #
O(N). Lookup the value for a key in the vector clock.
toList :: VectorClock a b -> [(a, b)] Source #
O(1). All the entries in the vector clock. Note that this is
not the inverse of fromList
.
Insertion
insert :: Ord a => a -> b -> VectorClock a b -> VectorClock a b Source #
O(N). Insert or replace the entry for a key.
inc :: (Ord a, Num b) => a -> VectorClock a b -> Maybe (VectorClock a b) Source #
O(N). Increment the entry for a key.
:: (Ord a, Num b) | |
=> a | key: the key of the entry |
-> VectorClock a b | vc: the vector clock |
-> b | default: if the key is not found, assume its value was the default and increment that |
-> VectorClock a b |
O(N). Increment the entry for a key. If the key does not exist, assume it was the default.
Deletion
delete :: Ord a => a -> VectorClock a b -> VectorClock a b Source #
O(N). Delete an entry from the vector clock. If the requested entry does not exist, does nothing.
Merges
:: (Ord a, Ord b) | |
=> (a -> Maybe b -> Maybe b -> Maybe b) | a function that takes the key, the value of the entry in the left hand vector clock, if it exists, the value in the right hand vector clock, if it exists, and, if it wishes to keep a value for this key in the resulting vector clock, returns it. |
-> VectorClock a b | lhs: the left hand vector clock |
-> VectorClock a b | rhs: the right hand vector clock |
-> VectorClock a b |
O(max(N, M)). Combine two vector clocks entry-by-entry.
max :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> VectorClock a b Source #
O(max(N, M)). The maximum of the two vector clocks.
diff :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> Maybe (VectorClock a b) Source #
O(M). If vc2
, compute the smallest causes
vc1vc3
s.t. max vc3 vc2 == vc1
. Note that the first parameter is the
newer vector clock.
Relations
The relations two vector clocks may find themselves in.
relation :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> Relation Source #
O(min(N, M)). The relation between the two vector clocks.
causes :: (Ord a, Ord b) => VectorClock a b -> VectorClock a b -> Bool Source #
O(min(N, M)). Short-hand for relation vc1 vc2 == Causes
.