mergeless-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Data.Mergeless

Contents

Description

A way to synchronise items without merge conflicts.

This concept has a few requirements:

  • Items must be immutable.
  • Items must allow for a centrally unique identifier.
  • Identifiers for items must be generatable in such a way that they are certainly unique.

Should mutation be a requirement, then it can be build such that it entails deleting the old version and creating a new version that is the modification of the old version.

There are a few obvious candidates for identifiers:

  • incremental identifiers
  • universally unique identifiers (recommended).

The typical setup is as follows:

  • A central server is set up to synchronise with
  • Each client synchronises with the central server, but never with eachother

A central server should operate as follows:

A client should operate as follows:

Synopsis

Documentation

data Added a Source #

A local item of type a that has been added but not synchronised yet

Constructors

Added 

Fields

Instances
Eq a => Eq (Added a) Source # 
Instance details

Defined in Data.Mergeless

Methods

(==) :: Added a -> Added a -> Bool #

(/=) :: Added a -> Added a -> Bool #

Ord a => Ord (Added a) Source # 
Instance details

Defined in Data.Mergeless

Methods

compare :: Added a -> Added a -> Ordering #

(<) :: Added a -> Added a -> Bool #

(<=) :: Added a -> Added a -> Bool #

(>) :: Added a -> Added a -> Bool #

(>=) :: Added a -> Added a -> Bool #

max :: Added a -> Added a -> Added a #

min :: Added a -> Added a -> Added a #

Show a => Show (Added a) Source # 
Instance details

Defined in Data.Mergeless

Methods

showsPrec :: Int -> Added a -> ShowS #

show :: Added a -> String #

showList :: [Added a] -> ShowS #

Generic (Added a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (Added a) :: * -> * #

Methods

from :: Added a -> Rep (Added a) x #

to :: Rep (Added a) x -> Added a #

ToJSON a => ToJSON (Added a) Source # 
Instance details

Defined in Data.Mergeless

FromJSON a => FromJSON (Added a) Source # 
Instance details

Defined in Data.Mergeless

Validity a => Validity (Added a) Source # 
Instance details

Defined in Data.Mergeless

Methods

validate :: Added a -> Validation #

type Rep (Added a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (Added a) = D1 (MetaData "Added" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" False) (C1 (MetaCons "Added" PrefixI True) (S1 (MetaSel (Just "addedValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "addedCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)))

data Synced i a Source #

A local item of type a with an identifier of type a that has been synchronised

Constructors

Synced 
Instances
(Eq i, Eq a) => Eq (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

(==) :: Synced i a -> Synced i a -> Bool #

(/=) :: Synced i a -> Synced i a -> Bool #

(Ord i, Ord a) => Ord (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

compare :: Synced i a -> Synced i a -> Ordering #

(<) :: Synced i a -> Synced i a -> Bool #

(<=) :: Synced i a -> Synced i a -> Bool #

(>) :: Synced i a -> Synced i a -> Bool #

(>=) :: Synced i a -> Synced i a -> Bool #

max :: Synced i a -> Synced i a -> Synced i a #

min :: Synced i a -> Synced i a -> Synced i a #

(Show i, Show a) => Show (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

showsPrec :: Int -> Synced i a -> ShowS #

show :: Synced i a -> String #

showList :: [Synced i a] -> ShowS #

Generic (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (Synced i a) :: * -> * #

Methods

from :: Synced i a -> Rep (Synced i a) x #

to :: Rep (Synced i a) x -> Synced i a #

(ToJSON i, ToJSON a) => ToJSON (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

toJSON :: Synced i a -> Value #

toEncoding :: Synced i a -> Encoding #

toJSONList :: [Synced i a] -> Value #

toEncodingList :: [Synced i a] -> Encoding #

(FromJSON i, FromJSON a) => FromJSON (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

parseJSON :: Value -> Parser (Synced i a) #

parseJSONList :: Value -> Parser [Synced i a] #

(Validity i, Validity a) => Validity (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

validate :: Synced i a -> Validation #

type Rep (Synced i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (Synced i a) = D1 (MetaData "Synced" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" False) (C1 (MetaCons "Synced" PrefixI True) ((S1 (MetaSel (Just "syncedUuid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 i) :*: S1 (MetaSel (Just "syncedValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) :*: (S1 (MetaSel (Just "syncedCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime) :*: S1 (MetaSel (Just "syncedSynced") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime))))

data StoreItem i a Source #

A store item with an Id of type i and a value of type a

Constructors

UnsyncedItem !(Added a)

A local item that has not been synchronised to the central store yet

SyncedItem !(Synced i a)

A local item that has been synchronised to the central store already

UndeletedItem !i

An item that has been synchronised to the central store, was subsequently deleted locally but this deletion has not been synchronised to the central store yet.

Instances
(Eq a, Eq i) => Eq (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

(==) :: StoreItem i a -> StoreItem i a -> Bool #

(/=) :: StoreItem i a -> StoreItem i a -> Bool #

(Ord a, Ord i) => Ord (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

compare :: StoreItem i a -> StoreItem i a -> Ordering #

(<) :: StoreItem i a -> StoreItem i a -> Bool #

(<=) :: StoreItem i a -> StoreItem i a -> Bool #

(>) :: StoreItem i a -> StoreItem i a -> Bool #

(>=) :: StoreItem i a -> StoreItem i a -> Bool #

max :: StoreItem i a -> StoreItem i a -> StoreItem i a #

min :: StoreItem i a -> StoreItem i a -> StoreItem i a #

(Show a, Show i) => Show (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

showsPrec :: Int -> StoreItem i a -> ShowS #

show :: StoreItem i a -> String #

showList :: [StoreItem i a] -> ShowS #

Generic (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (StoreItem i a) :: * -> * #

Methods

from :: StoreItem i a -> Rep (StoreItem i a) x #

to :: Rep (StoreItem i a) x -> StoreItem i a #

(ToJSON i, ToJSON a) => ToJSON (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

(FromJSON i, FromJSON a) => FromJSON (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

(Validity i, Validity a) => Validity (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

validate :: StoreItem i a -> Validation #

type Rep (StoreItem i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (StoreItem i a) = D1 (MetaData "StoreItem" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" False) (C1 (MetaCons "UnsyncedItem" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Added a))) :+: (C1 (MetaCons "SyncedItem" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Synced i a))) :+: C1 (MetaCons "UndeletedItem" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 i))))

newtype Store i a Source #

A client-side store of items with Id's of type i and values of type a

Constructors

Store 

Fields

Instances
(Eq a, Eq i) => Eq (Store i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

(==) :: Store i a -> Store i a -> Bool #

(/=) :: Store i a -> Store i a -> Bool #

(Ord a, Ord i) => Ord (Store i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

compare :: Store i a -> Store i a -> Ordering #

(<) :: Store i a -> Store i a -> Bool #

(<=) :: Store i a -> Store i a -> Bool #

(>) :: Store i a -> Store i a -> Bool #

(>=) :: Store i a -> Store i a -> Bool #

max :: Store i a -> Store i a -> Store i a #

min :: Store i a -> Store i a -> Store i a #

(Show a, Show i) => Show (Store i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

showsPrec :: Int -> Store i a -> ShowS #

show :: Store i a -> String #

showList :: [Store i a] -> ShowS #

Generic (Store i a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (Store i a) :: * -> * #

Methods

from :: Store i a -> Rep (Store i a) x #

to :: Rep (Store i a) x -> Store i a #

(ToJSON i, ToJSON a) => ToJSON (Store i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

toJSON :: Store i a -> Value #

toEncoding :: Store i a -> Encoding #

toJSONList :: [Store i a] -> Value #

toEncodingList :: [Store i a] -> Encoding #

(Ord a, Ord i, FromJSON i, FromJSON a) => FromJSON (Store i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

parseJSON :: Value -> Parser (Store i a) #

parseJSONList :: Value -> Parser [Store i a] #

(Validity i, Validity a, Ord i, Ord a) => Validity (Store i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

validate :: Store i a -> Validation #

type Rep (Store i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (Store i a) = D1 (MetaData "Store" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" True) (C1 (MetaCons "Store" PrefixI True) (S1 (MetaSel (Just "storeItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (StoreItem i a)))))

emptyStore :: Store i a Source #

The store with no items.

storeSize :: Store i a -> Int Source #

The number of items in a store

addItemToStore :: (Ord i, Ord a) => Added a -> Store i a -> Store i a Source #

Add a new (unsynced) item to the store

deleteUnsynced :: (Ord i, Ord a) => Added a -> Store i a -> Store i a Source #

deleteSynced :: (Ord i, Ord a) => Synced i a -> Store i a -> Store i a Source #

data SyncRequest i a Source #

A synchronisation request for items with identifiers of type i and values of type a

Instances
(Eq a, Eq i) => Eq (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

(==) :: SyncRequest i a -> SyncRequest i a -> Bool #

(/=) :: SyncRequest i a -> SyncRequest i a -> Bool #

(Ord a, Ord i) => Ord (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

compare :: SyncRequest i a -> SyncRequest i a -> Ordering #

(<) :: SyncRequest i a -> SyncRequest i a -> Bool #

(<=) :: SyncRequest i a -> SyncRequest i a -> Bool #

(>) :: SyncRequest i a -> SyncRequest i a -> Bool #

(>=) :: SyncRequest i a -> SyncRequest i a -> Bool #

max :: SyncRequest i a -> SyncRequest i a -> SyncRequest i a #

min :: SyncRequest i a -> SyncRequest i a -> SyncRequest i a #

(Show a, Show i) => Show (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

showsPrec :: Int -> SyncRequest i a -> ShowS #

show :: SyncRequest i a -> String #

showList :: [SyncRequest i a] -> ShowS #

Generic (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (SyncRequest i a) :: * -> * #

Methods

from :: SyncRequest i a -> Rep (SyncRequest i a) x #

to :: Rep (SyncRequest i a) x -> SyncRequest i a #

(ToJSON i, ToJSON a) => ToJSON (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

(FromJSON i, FromJSON a, Ord i, Ord a) => FromJSON (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

(Validity i, Validity a, Ord i, Ord a) => Validity (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

validate :: SyncRequest i a -> Validation #

type Rep (SyncRequest i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (SyncRequest i a) = D1 (MetaData "SyncRequest" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" False) (C1 (MetaCons "SyncRequest" PrefixI True) (S1 (MetaSel (Just "syncRequestAddedItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set (Added a))) :*: (S1 (MetaSel (Just "syncRequestSyncedItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set i)) :*: S1 (MetaSel (Just "syncRequestUndeletedItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set i)))))

data SyncResponse i a Source #

A synchronisation response for items with identifiers of type i and values of type a

Instances
(Eq i, Eq a) => Eq (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

(==) :: SyncResponse i a -> SyncResponse i a -> Bool #

(/=) :: SyncResponse i a -> SyncResponse i a -> Bool #

(Ord i, Ord a) => Ord (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

(Show i, Show a) => Show (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

Generic (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (SyncResponse i a) :: * -> * #

Methods

from :: SyncResponse i a -> Rep (SyncResponse i a) x #

to :: Rep (SyncResponse i a) x -> SyncResponse i a #

(ToJSON i, ToJSON a) => ToJSON (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

(FromJSON i, FromJSON a, Ord i, Ord a) => FromJSON (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

(Validity i, Validity a, Ord i, Ord a) => Validity (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (SyncResponse i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (SyncResponse i a) = D1 (MetaData "SyncResponse" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" False) (C1 (MetaCons "SyncResponse" PrefixI True) (S1 (MetaSel (Just "syncResponseAddedItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set (Synced i a))) :*: (S1 (MetaSel (Just "syncResponseNewRemoteItems") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set (Synced i a))) :*: S1 (MetaSel (Just "syncResponseItemsToBeDeletedLocally") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Set i)))))

Client-side Synchronisation

makeSyncRequest :: (Ord i, Ord a) => Store i a -> SyncRequest i a Source #

Produce a synchronisation request for a client-side store.

This request can then be sent to a central store for synchronisation.

mergeSyncResponse :: (Ord i, Ord a) => Store i a -> SyncResponse i a -> Store i a Source #

Merge a synchronisation response back into a client-side store.

Server-side Synchronisation

General synchronisation

data SyncProcessor i a m Source #

A record of the basic operations that are necessary to build a synchronisation processor.

Constructors

SyncProcessor 

Fields

Instances
Generic (SyncProcessor i a m) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (SyncProcessor i a m) :: * -> * #

Methods

from :: SyncProcessor i a m -> Rep (SyncProcessor i a m) x #

to :: Rep (SyncProcessor i a m) x -> SyncProcessor i a m #

type Rep (SyncProcessor i a m) Source # 
Instance details

Defined in Data.Mergeless

type Rep (SyncProcessor i a m) = D1 (MetaData "SyncProcessor" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" False) (C1 (MetaCons "SyncProcessor" PrefixI True) ((S1 (MetaSel (Just "syncProcessorDeleteMany") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set i -> m ())) :*: S1 (MetaSel (Just "syncProcessorQuerySynced") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set i -> m (Set i)))) :*: (S1 (MetaSel (Just "syncProcessorQueryNewRemote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set i -> m (Set (Synced i a)))) :*: S1 (MetaSel (Just "syncProcessorInsertMany") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (Synced i a) -> m ())))))

processSyncCustom :: forall i a m. (Ord i, Ord a, Monad m) => m i -> UTCTime -> SyncProcessor i a m -> SyncRequest i a -> m (SyncResponse i a) Source #

Process a server-side synchronisation request using a custom synchronisation processor

WARNING: The identifier generation function must produce newly unique identifiers such that each new item gets a unique identifier.

You can use this function with deterministically-random identifiers or incrementing identifiers.

Synchronisation with a simple central store

newtype CentralStore i a Source #

A central store of items with identifiers of type i and values of type a

Constructors

CentralStore 
Instances
(Eq i, Eq a) => Eq (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

Methods

(==) :: CentralStore i a -> CentralStore i a -> Bool #

(/=) :: CentralStore i a -> CentralStore i a -> Bool #

(Ord i, Ord a) => Ord (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

(Show i, Show a) => Show (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

Generic (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (CentralStore i a) :: * -> * #

Methods

from :: CentralStore i a -> Rep (CentralStore i a) x #

to :: Rep (CentralStore i a) x -> CentralStore i a #

(ToJSON a, ToJSONKey i) => ToJSON (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

(FromJSONKey i, Ord i, FromJSON a) => FromJSON (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

(Validity i, Validity a, Ord i, Ord a) => Validity (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (CentralStore i a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (CentralStore i a) = D1 (MetaData "CentralStore" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" True) (C1 (MetaCons "CentralStore" PrefixI True) (S1 (MetaSel (Just "centralStoreItems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map i (CentralItem a)))))

data CentralItem a Source #

An item in a central store with a value of type a

Instances
Eq a => Eq (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

Ord a => Ord (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

Show a => Show (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

Generic (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

Associated Types

type Rep (CentralItem a) :: * -> * #

Methods

from :: CentralItem a -> Rep (CentralItem a) x #

to :: Rep (CentralItem a) x -> CentralItem a #

ToJSON a => ToJSON (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

FromJSON a => FromJSON (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

Validity a => Validity (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (CentralItem a) Source # 
Instance details

Defined in Data.Mergeless

type Rep (CentralItem a) = D1 (MetaData "CentralItem" "Data.Mergeless" "mergeless-0.1.0.0-AHeGozk6NfTDJb9cYjJ6SL" False) (C1 (MetaCons "CentralItem" PrefixI True) (S1 (MetaSel (Just "centralValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: (S1 (MetaSel (Just "centralSynced") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime) :*: S1 (MetaSel (Just "centralCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime))))

processSyncWith :: forall i a m. (Ord i, Ord a, Monad m) => m i -> UTCTime -> CentralStore i a -> SyncRequest i a -> m (SyncResponse i a, CentralStore i a) Source #

Process a server-side synchronisation request using a time of syncing, and an identifier generation function.

see processSyncCustom

processSync :: (Ord i, Ord a, MonadIO m) => m i -> CentralStore i a -> SyncRequest i a -> m (SyncResponse i a, CentralStore i a) Source #

Process a server-side synchronisation request using getCurrentTime

see processSyncCustom