appendful-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

Data.Appendful.Collection

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 monotone identifier.
  • Items must allow for a client-side unique identifier.
  • Identifiers for items must be generated in such a way that they are certainly unique.

Should mutation be a requirement, then there is another library: mergeful for exactly this purpose.

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 ClientStore ci si a Source #

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

Constructors

ClientStore 

Fields

Instances

Instances details
(Eq ci, Eq a, Eq si) => Eq (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

(==) :: ClientStore ci si a -> ClientStore ci si a -> Bool #

(/=) :: ClientStore ci si a -> ClientStore ci si a -> Bool #

(Ord ci, Ord a, Ord si) => Ord (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

compare :: ClientStore ci si a -> ClientStore ci si a -> Ordering #

(<) :: ClientStore ci si a -> ClientStore ci si a -> Bool #

(<=) :: ClientStore ci si a -> ClientStore ci si a -> Bool #

(>) :: ClientStore ci si a -> ClientStore ci si a -> Bool #

(>=) :: ClientStore ci si a -> ClientStore ci si a -> Bool #

max :: ClientStore ci si a -> ClientStore ci si a -> ClientStore ci si a #

min :: ClientStore ci si a -> ClientStore ci si a -> ClientStore ci si a #

(Show ci, Show a, Show si) => Show (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

showsPrec :: Int -> ClientStore ci si a -> ShowS #

show :: ClientStore ci si a -> String #

showList :: [ClientStore ci si a] -> ShowS #

Generic (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Associated Types

type Rep (ClientStore ci si a) :: Type -> Type #

Methods

from :: ClientStore ci si a -> Rep (ClientStore ci si a) x #

to :: Rep (ClientStore ci si a) x -> ClientStore ci si a #

(Ord ci, Ord si, FromJSONKey ci, FromJSONKey si, ToJSONKey ci, ToJSONKey si, HasCodec si, HasCodec a, Eq a) => ToJSON (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

toJSON :: ClientStore ci si a -> Value #

toEncoding :: ClientStore ci si a -> Encoding #

toJSONList :: [ClientStore ci si a] -> Value #

toEncodingList :: [ClientStore ci si a] -> Encoding #

(Ord ci, Ord si, FromJSONKey ci, FromJSONKey si, ToJSONKey ci, ToJSONKey si, HasCodec si, HasCodec a, Eq a) => FromJSON (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

parseJSON :: Value -> Parser (ClientStore ci si a) #

parseJSONList :: Value -> Parser [ClientStore ci si a] #

(Ord ci, FromJSONKey ci, ToJSONKey ci, Ord si, FromJSONKey si, ToJSONKey si, HasCodec si, Eq a, HasCodec a) => HasCodec (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

(NFData ci, NFData si, NFData a) => NFData (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

rnf :: ClientStore ci si a -> () #

(Validity ci, Validity si, Validity a, Show ci, Show si, Ord ci, Ord si) => Validity (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

validate :: ClientStore ci si a -> Validation #

type Rep (ClientStore ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep (ClientStore ci si a) = D1 ('MetaData "ClientStore" "Data.Appendful.Collection" "appendful-0.1.0.0-ABO3BOJJQ2a6D3mhmHjiRw" 'False) (C1 ('MetaCons "ClientStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientStoreAdded") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map ci a)) :*: S1 ('MetaSel ('Just "clientStoreSynced") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map si a))))

data SyncRequest ci si a Source #

A synchronisation request for items with Client Id's of type ci, Server Id's of type i and values of type a

Constructors

SyncRequest 

Fields

Instances

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

Defined in Data.Appendful.Collection

Methods

(==) :: SyncRequest ci si a -> SyncRequest ci si a -> Bool #

(/=) :: SyncRequest ci si a -> SyncRequest ci si a -> Bool #

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

Defined in Data.Appendful.Collection

Methods

compare :: SyncRequest ci si a -> SyncRequest ci si a -> Ordering #

(<) :: SyncRequest ci si a -> SyncRequest ci si a -> Bool #

(<=) :: SyncRequest ci si a -> SyncRequest ci si a -> Bool #

(>) :: SyncRequest ci si a -> SyncRequest ci si a -> Bool #

(>=) :: SyncRequest ci si a -> SyncRequest ci si a -> Bool #

max :: SyncRequest ci si a -> SyncRequest ci si a -> SyncRequest ci si a #

min :: SyncRequest ci si a -> SyncRequest ci si a -> SyncRequest ci si a #

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

Defined in Data.Appendful.Collection

Methods

showsPrec :: Int -> SyncRequest ci si a -> ShowS #

show :: SyncRequest ci si a -> String #

showList :: [SyncRequest ci si a] -> ShowS #

Generic (SyncRequest ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Associated Types

type Rep (SyncRequest ci si a) :: Type -> Type #

Methods

from :: SyncRequest ci si a -> Rep (SyncRequest ci si a) x #

to :: Rep (SyncRequest ci si a) x -> SyncRequest ci si a #

(Ord ci, Ord si, FromJSONKey ci, FromJSONKey si, ToJSONKey ci, ToJSONKey si, HasCodec si, HasCodec a, Eq a) => ToJSON (SyncRequest ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

toJSON :: SyncRequest ci si a -> Value #

toEncoding :: SyncRequest ci si a -> Encoding #

toJSONList :: [SyncRequest ci si a] -> Value #

toEncodingList :: [SyncRequest ci si a] -> Encoding #

(Ord ci, Ord si, FromJSONKey ci, FromJSONKey si, ToJSONKey ci, ToJSONKey si, HasCodec si, HasCodec a, Eq a) => FromJSON (SyncRequest ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

parseJSON :: Value -> Parser (SyncRequest ci si a) #

parseJSONList :: Value -> Parser [SyncRequest ci si a] #

(Ord ci, FromJSONKey ci, ToJSONKey ci, Ord si, FromJSONKey si, ToJSONKey si, HasCodec si, Eq a, HasCodec a) => HasCodec (SyncRequest ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

(NFData ci, NFData si, NFData a) => NFData (SyncRequest ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

rnf :: SyncRequest ci si a -> () #

(Validity ci, Validity si, Validity a, Ord ci, Ord si, Show ci) => Validity (SyncRequest ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

validate :: SyncRequest ci si a -> Validation #

type Rep (SyncRequest ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep (SyncRequest ci si a) = D1 ('MetaData "SyncRequest" "Data.Appendful.Collection" "appendful-0.1.0.0-ABO3BOJJQ2a6D3mhmHjiRw" 'False) (C1 ('MetaCons "SyncRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "syncRequestAdded") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map ci a)) :*: S1 ('MetaSel ('Just "syncRequestMaximumSynced") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe si))))

data SyncResponse ci si a Source #

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

Constructors

SyncResponse 

Fields

Instances

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

Defined in Data.Appendful.Collection

Methods

(==) :: SyncResponse ci si a -> SyncResponse ci si a -> Bool #

(/=) :: SyncResponse ci si a -> SyncResponse ci si a -> Bool #

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

Defined in Data.Appendful.Collection

Methods

compare :: SyncResponse ci si a -> SyncResponse ci si a -> Ordering #

(<) :: SyncResponse ci si a -> SyncResponse ci si a -> Bool #

(<=) :: SyncResponse ci si a -> SyncResponse ci si a -> Bool #

(>) :: SyncResponse ci si a -> SyncResponse ci si a -> Bool #

(>=) :: SyncResponse ci si a -> SyncResponse ci si a -> Bool #

max :: SyncResponse ci si a -> SyncResponse ci si a -> SyncResponse ci si a #

min :: SyncResponse ci si a -> SyncResponse ci si a -> SyncResponse ci si a #

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

Defined in Data.Appendful.Collection

Methods

showsPrec :: Int -> SyncResponse ci si a -> ShowS #

show :: SyncResponse ci si a -> String #

showList :: [SyncResponse ci si a] -> ShowS #

Generic (SyncResponse ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Associated Types

type Rep (SyncResponse ci si a) :: Type -> Type #

Methods

from :: SyncResponse ci si a -> Rep (SyncResponse ci si a) x #

to :: Rep (SyncResponse ci si a) x -> SyncResponse ci si a #

(Ord ci, Ord si, FromJSONKey ci, FromJSONKey si, ToJSONKey ci, ToJSONKey si, HasCodec ci, HasCodec si, HasCodec a, Eq a) => ToJSON (SyncResponse ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

toJSON :: SyncResponse ci si a -> Value #

toEncoding :: SyncResponse ci si a -> Encoding #

toJSONList :: [SyncResponse ci si a] -> Value #

toEncodingList :: [SyncResponse ci si a] -> Encoding #

(Ord ci, Ord si, FromJSONKey ci, FromJSONKey si, ToJSONKey ci, ToJSONKey si, HasCodec ci, HasCodec si, HasCodec a, Eq a) => FromJSON (SyncResponse ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

parseJSON :: Value -> Parser (SyncResponse ci si a) #

parseJSONList :: Value -> Parser [SyncResponse ci si a] #

(Ord ci, FromJSONKey ci, ToJSONKey ci, HasCodec ci, Ord si, FromJSONKey si, ToJSONKey si, HasCodec si, Eq a, HasCodec a) => HasCodec (SyncResponse ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

(NFData ci, NFData si, NFData a) => NFData (SyncResponse ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

rnf :: SyncResponse ci si a -> () #

(Validity ci, Validity si, Validity a, Show ci, Show si, Ord ci, Ord si) => Validity (SyncResponse ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

validate :: SyncResponse ci si a -> Validation #

type Rep (SyncResponse ci si a) Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep (SyncResponse ci si a) = D1 ('MetaData "SyncResponse" "Data.Appendful.Collection" "appendful-0.1.0.0-ABO3BOJJQ2a6D3mhmHjiRw" 'False) (C1 ('MetaCons "SyncResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "syncResponseClientAdded") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map ci si)) :*: S1 ('MetaSel ('Just "syncResponseServerAdded") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map si a))))

Client-side Synchronisation

General

data ClientSyncProcessor ci si a m Source #

Instances

Instances details
Generic (ClientSyncProcessor ci si a m) Source # 
Instance details

Defined in Data.Appendful.Collection

Associated Types

type Rep (ClientSyncProcessor ci si a m) :: Type -> Type #

Methods

from :: ClientSyncProcessor ci si a m -> Rep (ClientSyncProcessor ci si a m) x #

to :: Rep (ClientSyncProcessor ci si a m) x -> ClientSyncProcessor ci si a m #

type Rep (ClientSyncProcessor ci si a m) Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep (ClientSyncProcessor ci si a m) = D1 ('MetaData "ClientSyncProcessor" "Data.Appendful.Collection" "appendful-0.1.0.0-ABO3BOJJQ2a6D3mhmHjiRw" 'False) (C1 ('MetaCons "ClientSyncProcessor" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientSyncProcessorSyncClientAdded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ci si -> m ())) :*: S1 ('MetaSel ('Just "clientSyncProcessorSyncServerAdded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map si a -> m ()))))

Pure

emptyClientStore :: ClientStore ci si a Source #

The client store with no items.

newtype ClientId Source #

A Client-side identifier for items for use with pure client stores

These only need to be unique at the client.

Constructors

ClientId 

Fields

Instances

Instances details
Bounded ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

Enum ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

Eq ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

Ord ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

Show ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

Generic ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

Associated Types

type Rep ClientId :: Type -> Type #

Methods

from :: ClientId -> Rep ClientId x #

to :: Rep ClientId x -> ClientId #

ToJSON ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

ToJSONKey ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

FromJSON ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

FromJSONKey ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

HasCodec ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

NFData ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

rnf :: ClientId -> () #

Validity ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep ClientId Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep ClientId = D1 ('MetaData "ClientId" "Data.Appendful.Collection" "appendful-0.1.0.0-ABO3BOJJQ2a6D3mhmHjiRw" 'True) (C1 ('MetaCons "ClientId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unClientId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

storeSize :: ClientStore ci si a -> Int Source #

The number of items in a store

This does not count the deleted items, so that those really look deleted.

addItemToClientStore :: (Enum ci, Bounded ci, Ord ci) => a -> ClientStore ci si a -> ClientStore ci si a Source #

Add an item to a client store as an added item.

This will take care of the uniqueness constraint of the cis in the map.

The values wrap around when reaching maxBound.

makeSyncRequest :: ClientStore ci si a -> SyncRequest ci si a Source #

Produce a synchronisation request for a client-side store.

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

mergeSyncResponse :: forall ci si a. (Ord ci, Ord si) => ClientStore ci si a -> SyncResponse ci si a -> ClientStore ci si a Source #

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

pureClientSyncProcessor :: forall ci si a. (Ord ci, Ord si) => ClientSyncProcessor ci si a (State (ClientStore ci si a)) Source #

Server-side Synchronisation

General synchronisation

data ServerSyncProcessor ci si a m Source #

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

Constructors

ServerSyncProcessor 

Fields

Instances

Instances details
Generic (ServerSyncProcessor ci si a m) Source # 
Instance details

Defined in Data.Appendful.Collection

Associated Types

type Rep (ServerSyncProcessor ci si a m) :: Type -> Type #

Methods

from :: ServerSyncProcessor ci si a m -> Rep (ServerSyncProcessor ci si a m) x #

to :: Rep (ServerSyncProcessor ci si a m) x -> ServerSyncProcessor ci si a m #

type Rep (ServerSyncProcessor ci si a m) Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep (ServerSyncProcessor ci si a m) = D1 ('MetaData "ServerSyncProcessor" "Data.Appendful.Collection" "appendful-0.1.0.0-ABO3BOJJQ2a6D3mhmHjiRw" 'False) (C1 ('MetaCons "ServerSyncProcessor" 'PrefixI 'True) (S1 ('MetaSel ('Just "serverSyncProcessorRead") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m (Map si a))) :*: S1 ('MetaSel ('Just "serverSyncProcessorAddItems") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ci a -> m (Map ci si)))))

processServerSyncCustom :: forall ci si a m. (Ord si, Monad m) => ServerSyncProcessor ci si a m -> SyncRequest ci si a -> m (SyncResponse ci si a) Source #

Synchronisation with a simple central store

newtype ServerStore si a Source #

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

Constructors

ServerStore 

Fields

Instances

Instances details
(Eq si, Eq a) => Eq (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

(==) :: ServerStore si a -> ServerStore si a -> Bool #

(/=) :: ServerStore si a -> ServerStore si a -> Bool #

(Ord si, Ord a) => Ord (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

compare :: ServerStore si a -> ServerStore si a -> Ordering #

(<) :: ServerStore si a -> ServerStore si a -> Bool #

(<=) :: ServerStore si a -> ServerStore si a -> Bool #

(>) :: ServerStore si a -> ServerStore si a -> Bool #

(>=) :: ServerStore si a -> ServerStore si a -> Bool #

max :: ServerStore si a -> ServerStore si a -> ServerStore si a #

min :: ServerStore si a -> ServerStore si a -> ServerStore si a #

(Show si, Show a) => Show (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

showsPrec :: Int -> ServerStore si a -> ShowS #

show :: ServerStore si a -> String #

showList :: [ServerStore si a] -> ShowS #

Generic (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Associated Types

type Rep (ServerStore si a) :: Type -> Type #

Methods

from :: ServerStore si a -> Rep (ServerStore si a) x #

to :: Rep (ServerStore si a) x -> ServerStore si a #

(Ord si, FromJSONKey si, ToJSONKey si, HasCodec a) => ToJSON (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

(Ord si, FromJSONKey si, ToJSONKey si, HasCodec a) => FromJSON (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

(Ord si, FromJSONKey si, ToJSONKey si, HasCodec a) => HasCodec (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

(NFData si, NFData a) => NFData (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

rnf :: ServerStore si a -> () #

(Validity si, Validity a, Show si, Show a, Ord si) => Validity (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

Methods

validate :: ServerStore si a -> Validation #

type Rep (ServerStore si a) Source # 
Instance details

Defined in Data.Appendful.Collection

type Rep (ServerStore si a) = D1 ('MetaData "ServerStore" "Data.Appendful.Collection" "appendful-0.1.0.0-ABO3BOJJQ2a6D3mhmHjiRw" 'True) (C1 ('MetaCons "ServerStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "serverStoreItems") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map si a))))

emptyServerStore :: ServerStore si a Source #

An empty central store to start with

processServerSync :: forall m ci si a. (Ord si, Monad m) => m si -> ServerStore si a -> SyncRequest ci si a -> m (SyncResponse ci si a, ServerStore si a) Source #

Process a server-side synchronisation request using a server id generator

see processSyncCustom