store-0.2.1.0: Fast binary serialization

Safe HaskellNone
LanguageHaskell2010

Data.Store.Version

Description

This module provides utilities which help ensure that we aren't attempting to de-serialize data that is an older or newer version. The WithVersion utility wraps up a datatype along with a version tag. This version tag can either be provided by the user (namedVersionConfig), or use a computed hash (hashedVersionConfig).

The magic here is using an SYB traversal (Data) to get the structure of all the data-types involved. This info is rendered to text and hashed to yield a hash which describes it.

NOTE that this API is still quite new and so is likely to break compatibility in the future. It should also be expected that the computed hashes may change between major version bumps, though this will be minimized when directly feasible.

Synopsis

Documentation

newtype StoreVersion Source #

Constructors

StoreVersion 

Instances

Eq StoreVersion Source # 
Data StoreVersion Source # 

Methods

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

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

toConstr :: StoreVersion -> Constr #

dataTypeOf :: StoreVersion -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> StoreVersion -> StoreVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StoreVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StoreVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> StoreVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StoreVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StoreVersion -> m StoreVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StoreVersion -> m StoreVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StoreVersion -> m StoreVersion #

Ord StoreVersion Source # 
Show StoreVersion Source # 
Generic StoreVersion Source # 

Associated Types

type Rep StoreVersion :: * -> * #

Store StoreVersion Source # 
type Rep StoreVersion Source # 
type Rep StoreVersion = D1 (MetaData "StoreVersion" "Data.Store.Version" "store-0.2.1.0-8oKO4N1LZvu1TLjxdOcnFl" True) (C1 (MetaCons "StoreVersion" PrefixI True) (S1 (MetaSel (Just Symbol "unStoreVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

data WithVersion a Source #

Constructors

WithVersion a StoreVersion 

Instances

Eq a => Eq (WithVersion a) Source # 
Data a => Data (WithVersion a) Source # 

Methods

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

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

toConstr :: WithVersion a -> Constr #

dataTypeOf :: WithVersion a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (WithVersion a) Source # 
Show a => Show (WithVersion a) Source # 
Generic (WithVersion a) Source # 

Associated Types

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

Methods

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

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

Store a => Store (WithVersion a) Source # 
type Rep (WithVersion a) Source # 
type Rep (WithVersion a) = D1 (MetaData "WithVersion" "Data.Store.Version" "store-0.2.1.0-8oKO4N1LZvu1TLjxdOcnFl" False) (C1 (MetaCons "WithVersion" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StoreVersion))))

data VersionConfig a Source #

Configuration for the version checking of a particular type.

Constructors

VersionConfig 

Fields

Instances

Eq (VersionConfig a) Source # 
Data a => Data (VersionConfig a) Source # 

Methods

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

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

toConstr :: VersionConfig a -> Constr #

dataTypeOf :: VersionConfig a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (VersionConfig a) Source # 
Generic (VersionConfig a) Source # 

Associated Types

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

type Rep (VersionConfig a) Source #