mergeful-0.3.0.0
Safe HaskellNone
LanguageHaskell2010

Data.Mergeful.Value

Description

A way to synchronise a single value with safe merge conflicts.

The 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 client should operate as follows:

For the first sychronisation

The client should ask the server for the current server value. The server should send over a Timed vaule, and the client should create its ClientValue with initialClientValue.

For any following synchronisation:

The central server should operate as follows:

WARNING: This whole approach can break down if a server resets its server times or if a client syncs with two different servers using the same server times.

Synopsis

Documentation

initialClientValue :: Timed a -> ClientValue a Source #

Produce a client value based on an initial synchronisation request

makeValueSyncRequest :: ClientValue a -> ValueSyncRequest a Source #

Produce an ItemSyncRequest from a ClientItem.

Send this to the server for synchronisation.

mergeValueSyncResponseRaw :: ClientValue a -> ValueSyncResponse a -> ValueMergeResult a Source #

Merge an ValueSyncResponse into the current ClientValue.

This function will not make any decisions about what to do with conflicts or mismatches between the request and the response. It only produces a ValueMergeResult so you can decide what to do with it.

data ValueMergeResult a Source #

Constructors

MergeSuccess !(ClientValue a)

The merger went succesfully, no conflicts or desyncs

MergeConflict !a !(Timed a)

The item at the server side

MergeMismatch

The server responded with a response that did not make sense given the client's request.

This should not happen in practice.

Instances

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

Defined in Data.Mergeful.Value

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

Defined in Data.Mergeful.Value

Generic (ValueMergeResult a) Source # 
Instance details

Defined in Data.Mergeful.Value

Associated Types

type Rep (ValueMergeResult a) :: Type -> Type #

NFData a => NFData (ValueMergeResult a) Source # 
Instance details

Defined in Data.Mergeful.Value

Methods

rnf :: ValueMergeResult a -> () #

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

Defined in Data.Mergeful.Value

type Rep (ValueMergeResult a) Source # 
Instance details

Defined in Data.Mergeful.Value

type Rep (ValueMergeResult a) = D1 ('MetaData "ValueMergeResult" "Data.Mergeful.Value" "mergeful-0.3.0.0-IufP8wiUmUb8vtwEhWnzS0" 'False) (C1 ('MetaCons "MergeSuccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ClientValue a))) :+: (C1 ('MetaCons "MergeConflict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Timed a))) :+: C1 ('MetaCons "MergeMismatch" 'PrefixI 'False) (U1 :: Type -> Type)))

mergeValueSyncResponseIgnoreProblems :: ClientValue a -> ValueSyncResponse a -> ClientValue a Source #

Resolve a ValueSyncResponse into the current ClientValue.

This function ignores any problems that may occur. In the case of a conclict, it will just not update the client item. The next sync request will then produce a conflict again.

mergeValueSyncResponseIgnoreProblems cs = mergeIgnoringProblems cs . mergeValueSyncResponseRaw cs

mergeIgnoringProblems :: ClientValue a -> ValueMergeResult a -> ClientValue a Source #

Ignore any merge problems in a ValueMergeResult.

This function just returns the original ClientValue if anything other than MergeSuccess occurs.

This function ignores any problems that may occur. In the case of a conclict, it will just not update the client item. The next sync request will then produce a conflict again.

Pro: does not lose data

Con: Clients will diverge when a conflict occurs

mergeFromServer :: ClientValue a -> ValueMergeResult a -> ClientValue a Source #

Resolve a ValueMergeResult by taking whatever the server gave the client.

Pro: Clients will converge on the same value.

Con: Conflicting updates will be lost.

mergeUsingFunction :: (a -> Timed a -> Timed a) -> ClientValue a -> ValueMergeResult a -> ClientValue a Source #

Resolve a ValueMergeResult using a given merge strategy.

This function ignores MergeMismatch and will just return the original ClientValue in that case.

In order for clients to converge on the same value correctly, this function must be:

  • Associative
  • Idempotent
  • The same on all clients

Server side

initialServerValue :: a -> ServerValue a Source #

Initialise a server value.

Note that the server has to start with a value, the value a cannot be omitted.

Types, for reference

data ChangedFlag Source #

Constructors

Changed 
NotChanged 

Instances

Instances details
Eq ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

Show ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

Generic ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

Associated Types

type Rep ChangedFlag :: Type -> Type #

ToJSON ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

FromJSON ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

NFData ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

Methods

rnf :: ChangedFlag -> () #

Validity ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

type Rep ChangedFlag Source # 
Instance details

Defined in Data.Mergeful.Value

type Rep ChangedFlag = D1 ('MetaData "ChangedFlag" "Data.Mergeful.Value" "mergeful-0.3.0.0-IufP8wiUmUb8vtwEhWnzS0" 'False) (C1 ('MetaCons "Changed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotChanged" 'PrefixI 'False) (U1 :: Type -> Type))

data ClientValue a Source #

The client side value.

The only differences between a and 'ClientValue a' are that 'ClientValue a' also remembers the last synchronisation time from the server, and whether the item has been modified at the client

There cannot be an unsynced ClientValue.

Instances

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

Defined in Data.Mergeful.Value

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

Defined in Data.Mergeful.Value

Generic (ClientValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

Associated Types

type Rep (ClientValue a) :: Type -> Type #

Methods

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

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

HasCodec a => ToJSON (ClientValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => FromJSON (ClientValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => HasCodec (ClientValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

NFData a => NFData (ClientValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

Methods

rnf :: ClientValue a -> () #

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

Defined in Data.Mergeful.Value

type Rep (ClientValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

type Rep (ClientValue a) = D1 ('MetaData "ClientValue" "Data.Mergeful.Value" "mergeful-0.3.0.0-IufP8wiUmUb8vtwEhWnzS0" 'False) (C1 ('MetaCons "ClientValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientValueTimedValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Timed a)) :*: S1 ('MetaSel ('Just "clientValueChanged") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChangedFlag)))

data ValueSyncRequest a Source #

Constructors

ValueSyncRequestKnown !ServerTime

There is an item locally that was synced at the given ServerTime

ValueSyncRequestKnownButChanged !(Timed a)

There is an item locally that was synced at the given ServerTime but it has been changed since then.

Instances

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

Defined in Data.Mergeful.Value

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

Defined in Data.Mergeful.Value

Generic (ValueSyncRequest a) Source # 
Instance details

Defined in Data.Mergeful.Value

Associated Types

type Rep (ValueSyncRequest a) :: Type -> Type #

HasCodec a => ToJSON (ValueSyncRequest a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => FromJSON (ValueSyncRequest a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => HasCodec (ValueSyncRequest a) Source # 
Instance details

Defined in Data.Mergeful.Value

NFData a => NFData (ValueSyncRequest a) Source # 
Instance details

Defined in Data.Mergeful.Value

Methods

rnf :: ValueSyncRequest a -> () #

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

Defined in Data.Mergeful.Value

type Rep (ValueSyncRequest a) Source # 
Instance details

Defined in Data.Mergeful.Value

type Rep (ValueSyncRequest a) = D1 ('MetaData "ValueSyncRequest" "Data.Mergeful.Value" "mergeful-0.3.0.0-IufP8wiUmUb8vtwEhWnzS0" 'False) (C1 ('MetaCons "ValueSyncRequestKnown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ServerTime)) :+: C1 ('MetaCons "ValueSyncRequestKnownButChanged" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Timed a))))

data ValueSyncResponse a Source #

Constructors

ValueSyncResponseInSync

The client and server are fully in sync.

Nothing needs to be done at the client side.

ValueSyncResponseClientChanged !ServerTime

The client changed the value and server has succesfully been made aware of that.

The client needs to update its server time

ValueSyncResponseServerChanged !(Timed a)

This value has been changed on the server side.

The client should change it too.

ValueSyncResponseConflict !(Timed a)

The item at the server side

Instances

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

Defined in Data.Mergeful.Value

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

Defined in Data.Mergeful.Value

Generic (ValueSyncResponse a) Source # 
Instance details

Defined in Data.Mergeful.Value

Associated Types

type Rep (ValueSyncResponse a) :: Type -> Type #

HasCodec a => ToJSON (ValueSyncResponse a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => FromJSON (ValueSyncResponse a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => HasCodec (ValueSyncResponse a) Source # 
Instance details

Defined in Data.Mergeful.Value

NFData a => NFData (ValueSyncResponse a) Source # 
Instance details

Defined in Data.Mergeful.Value

Methods

rnf :: ValueSyncResponse a -> () #

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

Defined in Data.Mergeful.Value

type Rep (ValueSyncResponse a) Source # 
Instance details

Defined in Data.Mergeful.Value

type Rep (ValueSyncResponse a) = D1 ('MetaData "ValueSyncResponse" "Data.Mergeful.Value" "mergeful-0.3.0.0-IufP8wiUmUb8vtwEhWnzS0" 'False) ((C1 ('MetaCons "ValueSyncResponseInSync" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValueSyncResponseClientChanged" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ServerTime))) :+: (C1 ('MetaCons "ValueSyncResponseServerChanged" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Timed a))) :+: C1 ('MetaCons "ValueSyncResponseConflict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Timed a)))))

newtype ServerValue a Source #

The server-side value.

The only difference between a and 'ServerValue a' is that 'ServerValue a' also remembers the last time this value was changed during synchronisation.

Constructors

ServerValue 

Fields

Instances

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

Defined in Data.Mergeful.Value

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

Defined in Data.Mergeful.Value

Generic (ServerValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

Associated Types

type Rep (ServerValue a) :: Type -> Type #

Methods

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

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

HasCodec a => ToJSON (ServerValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => FromJSON (ServerValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

HasCodec a => HasCodec (ServerValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

NFData a => NFData (ServerValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

Methods

rnf :: ServerValue a -> () #

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

Defined in Data.Mergeful.Value

type Rep (ServerValue a) Source # 
Instance details

Defined in Data.Mergeful.Value

type Rep (ServerValue a) = D1 ('MetaData "ServerValue" "Data.Mergeful.Value" "mergeful-0.3.0.0-IufP8wiUmUb8vtwEhWnzS0" 'True) (C1 ('MetaCons "ServerValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "unServerValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Timed a))))