| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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:
- The server accepts a
SyncRequest. - The server performs operations according to the functionality of
processSync. - The server respons with a
SyncResponse.
A client should operate as follows:
- The client produces a
SyncRequestwithmakeSyncRequest. - The client sends that request to the central server and gets a
SyncResponse. - The client then updates its local store with
mergeSyncResponse.
Synopsis
- data Added a = Added {
- addedValue :: !a
- addedCreated :: !UTCTime
- data Synced i a = Synced {
- syncedUuid :: i
- syncedValue :: !a
- syncedCreated :: !UTCTime
- syncedSynced :: !UTCTime
- data StoreItem i a
- = UnsyncedItem !(Added a)
- | SyncedItem !(Synced i a)
- | UndeletedItem !i
- newtype Store i a = Store {
- storeItems :: Set (StoreItem i a)
- emptyStore :: Store i a
- storeSize :: Store i a -> Int
- addItemToStore :: (Ord i, Ord a) => Added a -> Store i a -> Store i a
- deleteUnsynced :: (Ord i, Ord a) => Added a -> Store i a -> Store i a
- deleteSynced :: (Ord i, Ord a) => Synced i a -> Store i a -> Store i a
- data SyncRequest i a = SyncRequest {
- syncRequestAddedItems :: !(Set (Added a))
- syncRequestSyncedItems :: !(Set i)
- syncRequestUndeletedItems :: !(Set i)
- data SyncResponse i a = SyncResponse {
- syncResponseAddedItems :: !(Set (Synced i a))
- syncResponseNewRemoteItems :: !(Set (Synced i a))
- syncResponseItemsToBeDeletedLocally :: !(Set i)
- makeSyncRequest :: (Ord i, Ord a) => Store i a -> SyncRequest i a
- mergeSyncResponse :: (Ord i, Ord a) => Store i a -> SyncResponse i a -> Store i a
- data SyncProcessor i a m = SyncProcessor {
- syncProcessorDeleteMany :: Set i -> m ()
- syncProcessorQuerySynced :: Set i -> m (Set i)
- syncProcessorQueryNewRemote :: Set i -> m (Set (Synced i a))
- syncProcessorInsertMany :: 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)
- newtype CentralStore i a = CentralStore {
- centralStoreItems :: Map i (CentralItem a)
- data CentralItem a = CentralItem {
- centralValue :: !a
- centralSynced :: !UTCTime
- centralCreated :: !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)
- processSync :: (Ord i, Ord a, MonadIO m) => m i -> CentralStore i a -> SyncRequest i a -> m (SyncResponse i a, CentralStore i a)
Documentation
A local item of type a that has been added but not synchronised yet
Constructors
| Added | |
Fields
| |
Instances
| Eq a => Eq (Added a) Source # | |
| Ord a => Ord (Added a) Source # | |
| Show a => Show (Added a) Source # | |
| Generic (Added a) Source # | |
| ToJSON a => ToJSON (Added a) Source # | |
Defined in Data.Mergeless | |
| FromJSON a => FromJSON (Added a) Source # | |
| Validity a => Validity (Added a) Source # | |
Defined in Data.Mergeless Methods validate :: Added a -> Validation # | |
| type Rep (Added a) Source # | |
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))) | |
A local item of type a with an identifier of type a that has been synchronised
Constructors
| Synced | |
Fields
| |
Instances
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
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 # | |
| (Ord a, Ord i) => Ord (Store i a) Source # | |
| (Show a, Show i) => Show (Store i a) Source # | |
| Generic (Store i a) Source # | |
| (ToJSON i, ToJSON a) => ToJSON (Store i a) Source # | |
Defined in Data.Mergeless | |
| (Ord a, Ord i, FromJSON i, FromJSON a) => FromJSON (Store i a) Source # | |
| (Validity i, Validity a, Ord i, Ord a) => Validity (Store i a) Source # | |
Defined in Data.Mergeless Methods validate :: Store i a -> Validation # | |
| type Rep (Store i a) Source # | |
Defined in Data.Mergeless | |
emptyStore :: Store i a Source #
The store with no items.
addItemToStore :: (Ord i, Ord a) => Added a -> Store i a -> Store i a Source #
Add a new (unsynced) item to the store
data SyncRequest i a Source #
A synchronisation request for items with identifiers of type i and values of type a
Constructors
| SyncRequest | |
Fields
| |
Instances
data SyncResponse i a Source #
A synchronisation response for items with identifiers of type i and values of type a
Constructors
| SyncResponse | |
Fields
| |
Instances
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
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 | |
Fields
| |
Instances
data CentralItem a Source #
An item in a central store with a value of type a
Constructors
| CentralItem | |
Fields
| |
Instances
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.
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