vector-clock-0.2.3: Vector clocks for versioning message flows

Safe HaskellSafe
LanguageHaskell98

Data.VectorClock.Simple

Contents

Description

A vector clock implementation in terms of simply-linked lists.

Synopsis

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 members, 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 inccrement 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 relationship, 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.

Instances

Functor (VectorClock a) Source # 

Methods

fmap :: (a -> b) -> VectorClock a a -> VectorClock a b #

(<$) :: a -> VectorClock a b -> VectorClock a a #

Foldable (VectorClock a) Source # 

Methods

fold :: Monoid m => VectorClock a m -> m #

foldMap :: Monoid m => (a -> m) -> VectorClock a a -> m #

foldr :: (a -> b -> b) -> b -> VectorClock a a -> b #

foldr' :: (a -> b -> b) -> b -> VectorClock a a -> b #

foldl :: (b -> a -> b) -> b -> VectorClock a a -> b #

foldl' :: (b -> a -> b) -> b -> VectorClock a a -> b #

foldr1 :: (a -> a -> a) -> VectorClock a a -> a #

foldl1 :: (a -> a -> a) -> VectorClock a a -> a #

toList :: VectorClock a a -> [a] #

null :: VectorClock a a -> Bool #

length :: VectorClock a a -> Int #

elem :: Eq a => a -> VectorClock a a -> Bool #

maximum :: Ord a => VectorClock a a -> a #

minimum :: Ord a => VectorClock a a -> a #

sum :: Num a => VectorClock a a -> a #

product :: Num a => VectorClock a a -> a #

Traversable (VectorClock a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> VectorClock a a -> f (VectorClock a b) #

sequenceA :: Applicative f => VectorClock a (f a) -> f (VectorClock a a) #

mapM :: Monad m => (a -> m b) -> VectorClock a a -> m (VectorClock a b) #

sequence :: Monad m => VectorClock a (m a) -> m (VectorClock a a) #

(Eq a, Eq b) => Eq (VectorClock a b) Source # 

Methods

(==) :: VectorClock a b -> VectorClock a b -> Bool #

(/=) :: VectorClock a b -> VectorClock a b -> Bool #

(Data a, Data b) => Data (VectorClock a b) Source # 

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> VectorClock a b -> c (VectorClock a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VectorClock a b) #

toConstr :: VectorClock a b -> Constr #

dataTypeOf :: VectorClock a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VectorClock a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VectorClock a b)) #

gmapT :: (forall c. Data c => c -> c) -> VectorClock a b -> VectorClock a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VectorClock a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VectorClock a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> VectorClock a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VectorClock a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VectorClock a b -> m (VectorClock a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VectorClock a b -> m (VectorClock a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VectorClock a b -> m (VectorClock a b) #

(Show a, Show b) => Show (VectorClock a b) Source # 

Methods

showsPrec :: Int -> VectorClock a b -> ShowS #

show :: VectorClock a b -> String #

showList :: [VectorClock a b] -> ShowS #

Generic (VectorClock a b) Source # 

Associated Types

type Rep (VectorClock a b) :: * -> * #

Methods

from :: VectorClock a b -> Rep (VectorClock a b) x #

to :: Rep (VectorClock a b) x -> VectorClock a b #

(Binary a, Binary b) => Binary (VectorClock a b) Source # 

Methods

put :: VectorClock a b -> Put #

get :: Get (VectorClock a b) #

putList :: [VectorClock a b] -> Put #

type Rep (VectorClock a b) Source # 
type Rep (VectorClock a b) = D1 (MetaData "VectorClock" "Data.VectorClock.Simple" "vector-clock-0.2.3-8Jlja8XE59BAbbotxKfijy" False) (C1 (MetaCons "VectorClock" PrefixI True) (S1 (MetaSel (Just Symbol "clock") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(a, b)])))

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.

incWithDefault Source #

Arguments

:: (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

combine Source #

Arguments

:: (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 causes vc1, compute the smallest vc3 s.t. max vc3 vc2 == vc1. Note that the first parameter is the newer vector clock.

Relations

data Relation Source #

The relations two vector clocks may find themselves in.

Constructors

Causes 
CausedBy 
Concurrent 

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.

Debugging

valid :: (Ord a, Ord b) => VectorClock a b -> Bool Source #

O(N). Check whether the vector clock is valid or not.