safecopy-0.10.1: Binary serialization with version control.

Safe HaskellNone
LanguageHaskell98

Data.SafeCopy.Internal

Synopsis

Documentation

class SafeCopy (MigrateFrom a) => Migrate a where Source #

The central mechanism for dealing with version control.

This type class specifies what data migrations can happen and how they happen.

Associated Types

type MigrateFrom a Source #

This is the type we're extending. Each type capable of migration can only extend one other type.

Methods

migrate :: MigrateFrom a -> a Source #

This method specifies how to migrate from the older type to the newer one. It will never be necessary to use this function manually as it all taken care of internally in the library.

Instances
Migrate Double Source # 
Instance details

Defined in Data.SafeCopy.Instances

Associated Types

type MigrateFrom Double :: Type Source #

Migrate Float Source # 
Instance details

Defined in Data.SafeCopy.Instances

Associated Types

type MigrateFrom Float :: Type Source #

newtype Reverse a Source #

This is a wrapper type used migrating backwards in the chain of compatible types.

Constructors

Reverse 

Fields

data Kind a where Source #

The kind of a data type determines how it is tagged (if at all).

Primitives kinds (see primitive) are not tagged with a version id and hence cannot be extended later.

Extensions (see extension) tells the system that there exists a previous version of the data type which should be migrated if needed.

There is also a default kind which is neither primitive nor is an extension of a previous type.

Constructors

Primitive :: Kind a 
Base :: Kind a 
Extends :: Migrate a => Proxy (MigrateFrom a) -> Kind a 
Extended :: Migrate (Reverse a) => Kind a -> Kind a 

newtype Prim a Source #

Wrapper for data that was saved without a version tag.

Constructors

Prim 

Fields

class SafeCopy a where Source #

The centerpiece of this library. Defines a version for a data type together with how it should be serialized/parsed.

Users should define instances of SafeCopy for their types even though getCopy and putCopy can't be used directly. To serialize/parse a data type using SafeCopy, see safeGet and safePut.

Minimal complete definition

Nothing

Methods

version :: Version a Source #

The version of the type.

Only used as a key so it must be unique (this is checked at run-time) but doesn't have to be sequential or continuous.

The default version is '0'.

kind :: Kind a Source #

The kind specifies how versions are dealt with. By default, values are tagged with their version id and don't have any previous versions. See extension and the much less used primitive.

getCopy :: Contained (Get a) Source #

This method defines how a value should be parsed without also worrying about writing out the version tag. This function cannot be used directly. One should use safeGet, instead.

putCopy :: a -> Contained Put Source #

This method defines how a value should be parsed without worrying about previous versions or migrations. This function cannot be used directly. One should use safeGet, instead.

internalConsistency :: Consistency a Source #

Internal function that should not be overrided. Consistent iff the version history is consistent (i.e. there are no duplicate version numbers) and the chain of migrations is valid.

This function is in the typeclass so that this information is calculated only once during the program lifetime, instead of everytime safeGet or safePut is used.

objectProfile :: Profile a Source #

Version profile.

errorTypeName :: Proxy a -> String Source #

The name of the type. This is only used in error message strings.

errorTypeName :: Typeable a => Proxy a -> String Source #

The name of the type. This is only used in error message strings.

putCopy :: (GPutCopy (Rep a) DatatypeInfo, Constructors a) => a -> Contained Put Source #

This method defines how a value should be parsed without worrying about previous versions or migrations. This function cannot be used directly. One should use safeGet, instead.

getCopy :: (GGetCopy (Rep a) DatatypeInfo, Constructors a) => Contained (Get a) Source #

This method defines how a value should be parsed without also worrying about writing out the version tag. This function cannot be used directly. One should use safeGet, instead.

Instances
SafeCopy Bool Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Char Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Double Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Float Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Int Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Int8 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Int16 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Int32 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Int64 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Integer Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Natural Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Ordering Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Word Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Word8 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Word16 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Word32 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Word64 Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy () Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy ByteString Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy ByteString Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy IntSet Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Month Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Day Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy ClockTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy CalendarTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy TimeDiff Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Text Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Text Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy ZonedTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy LocalTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy TimeOfDay Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy TimeZone Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy UniversalTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy UTCTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy NominalDiffTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy AbsoluteTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy DiffTime Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy Day Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy a => SafeCopy [a] Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy a => SafeCopy (Maybe a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(Integral a, SafeCopy a) => SafeCopy (Ratio a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(HasResolution a, Fractional (Fixed a), Typeable a) => SafeCopy (Fixed a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy a => SafeCopy (NonEmpty a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy a => SafeCopy (IntMap a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy a => SafeCopy (Tree a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy a => SafeCopy (Seq a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy a, Ord a) => SafeCopy (Set a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy' a, Unbox a) => SafeCopy (Vector a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy' a, Storable a) => SafeCopy (Vector a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy' a, Prim a) => SafeCopy (Vector a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy' a => SafeCopy (Vector a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

SafeCopy' a => SafeCopy (Prim a) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy a, SafeCopy b) => SafeCopy (Either a b) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy a, SafeCopy b) => SafeCopy (a, b) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(IArray UArray e, Ix i, SafeCopy e, SafeCopy i) => SafeCopy (UArray i e) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(Ix i, SafeCopy e, SafeCopy i) => SafeCopy (Array i e) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy a, SafeCopy b, Ord a) => SafeCopy (Map a b) Source # 
Instance details

Defined in Data.SafeCopy.Instances

(SafeCopy' a, SafeCopy' b, SafeCopy' c) => SafeCopy (a, b, c) Source # 
Instance details

Defined in Data.SafeCopy.Instances

Methods

version :: Version (a, b, c) Source #

kind :: Kind (a, b, c) Source #

getCopy :: Contained (Get (a, b, c)) Source #

putCopy :: (a, b, c) -> Contained Put Source #

internalConsistency :: Consistency (a, b, c) Source #

objectProfile :: Profile (a, b, c) Source #

errorTypeName :: Proxy (a, b, c) -> String Source #

(SafeCopy' a, SafeCopy' b, SafeCopy' c, SafeCopy' d) => SafeCopy (a, b, c, d) Source # 
Instance details

Defined in Data.SafeCopy.Instances

Methods

version :: Version (a, b, c, d) Source #

kind :: Kind (a, b, c, d) Source #

getCopy :: Contained (Get (a, b, c, d)) Source #

putCopy :: (a, b, c, d) -> Contained Put Source #

internalConsistency :: Consistency (a, b, c, d) Source #

objectProfile :: Profile (a, b, c, d) Source #

errorTypeName :: Proxy (a, b, c, d) -> String Source #

(SafeCopy' a, SafeCopy' b, SafeCopy' c, SafeCopy' d, SafeCopy' e) => SafeCopy (a, b, c, d, e) Source # 
Instance details

Defined in Data.SafeCopy.Instances

Methods

version :: Version (a, b, c, d, e) Source #

kind :: Kind (a, b, c, d, e) Source #

getCopy :: Contained (Get (a, b, c, d, e)) Source #

putCopy :: (a, b, c, d, e) -> Contained Put Source #

internalConsistency :: Consistency (a, b, c, d, e) Source #

objectProfile :: Profile (a, b, c, d, e) Source #

errorTypeName :: Proxy (a, b, c, d, e) -> String Source #

(SafeCopy' a, SafeCopy' b, SafeCopy' c, SafeCopy' d, SafeCopy' e, SafeCopy' f) => SafeCopy (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.SafeCopy.Instances

Methods

version :: Version (a, b, c, d, e, f) Source #

kind :: Kind (a, b, c, d, e, f) Source #

getCopy :: Contained (Get (a, b, c, d, e, f)) Source #

putCopy :: (a, b, c, d, e, f) -> Contained Put Source #

internalConsistency :: Consistency (a, b, c, d, e, f) Source #

objectProfile :: Profile (a, b, c, d, e, f) Source #

errorTypeName :: Proxy (a, b, c, d, e, f) -> String Source #

(SafeCopy' a, SafeCopy' b, SafeCopy' c, SafeCopy' d, SafeCopy' e, SafeCopy' f, SafeCopy' g) => SafeCopy (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.SafeCopy.Instances

Methods

version :: Version (a, b, c, d, e, f, g) Source #

kind :: Kind (a, b, c, d, e, f, g) Source #

getCopy :: Contained (Get (a, b, c, d, e, f, g)) Source #

putCopy :: (a, b, c, d, e, f, g) -> Contained Put Source #

internalConsistency :: Consistency (a, b, c, d, e, f, g) Source #

objectProfile :: Profile (a, b, c, d, e, f, g) Source #

errorTypeName :: Proxy (a, b, c, d, e, f, g) -> String Source #

class GPutCopy f p where Source #

Methods

gputCopy :: p -> f p -> Put Source #

Instances
(GPutCopy f p, GPutCopy g p) => GPutCopy (f :+: g) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputCopy :: p -> (f :+: g) p -> Put Source #

GPutCopy a p => GPutCopy (M1 D c a) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputCopy :: p -> M1 D c a p -> Put Source #

(GPutFields a p, p ~ DatatypeInfo) => GPutCopy (M1 C c a) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputCopy :: p -> M1 C c a p -> Put Source #

type SafeCopy' a = (SafeCopy a, Typeable a) Source #

A constraint that combines SafeCopy and Typeable.

class GPutFields f p where Source #

gputFields traverses the fields of a constructor and returns a put for the safecopy versions and a put for the field values.

Methods

gputFields :: p -> f p -> RWST () [Put] (Set TypeRep) PutM () Source #

Instances
GPutFields (V1 :: Type -> Type) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputFields :: p -> V1 p -> RWST () [Put] (Set TypeRep) PutM () Source #

GPutFields (U1 :: Type -> Type) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputFields :: p -> U1 p -> RWST () [Put] (Set TypeRep) PutM () Source #

SafeCopy' a => GPutFields (K1 R a :: Type -> Type) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputFields :: p -> K1 R a p -> RWST () [Put] (Set TypeRep) PutM () Source #

(GPutFields f p, GPutFields g p) => GPutFields (f :*: g) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputFields :: p -> (f :*: g) p -> RWST () [Put] (Set TypeRep) PutM () Source #

GPutFields f p => GPutFields (M1 S c f) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

gputFields :: p -> M1 S c f p -> RWST () [Put] (Set TypeRep) PutM () Source #

class GGetCopy f p where Source #

Methods

ggetCopy :: p -> Get (f a) Source #

Instances
(GGetCopy f p, GGetCopy g p, p ~ DatatypeInfo) => GGetCopy (f :+: g) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetCopy :: p -> Get ((f :+: g) a) Source #

(GGetCopy f p, p ~ DatatypeInfo) => GGetCopy (M1 D d f) p Source #

The M1 type has a fourth type parameter p:

newtype M1 i (c :: Meta) (f :: k -> *) (p :: k) = M1 {unM1 :: f p}

Note that the type of the M1 field is f p, so in order to express this type we add a parameter of type p that we can apply to values of type f.

Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetCopy :: p -> Get (M1 D d f a) Source #

GGetFields f p => GGetCopy (M1 C c f) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetCopy :: p -> Get (M1 C c f a) Source #

class GGetFields f p where Source #

Methods

ggetFields :: p -> StateT (Map TypeRep Int32) Get (Get (f a)) Source #

Instances
GGetFields (V1 :: Type -> Type) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetFields :: p -> StateT (Map TypeRep Int32) Get (Get (V1 a)) Source #

GGetFields (U1 :: Type -> Type) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetFields :: p -> StateT (Map TypeRep Int32) Get (Get (U1 a)) Source #

SafeCopy' a => GGetFields (K1 R a :: Type -> Type) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetFields :: p -> StateT (Map TypeRep Int32) Get (Get (K1 R a a0)) Source #

(GGetFields f p, GGetFields g p) => GGetFields (f :*: g) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetFields :: p -> StateT (Map TypeRep Int32) Get (Get ((f :*: g) a)) Source #

GGetFields f p => GGetFields (M1 S c f) p Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

ggetFields :: p -> StateT (Map TypeRep Int32) Get (Get (M1 S c f a)) Source #

data DatatypeInfo Source #

Constructors

ConstructorCount 

Fields

ConstructorInfo 

Fields

Instances
Show DatatypeInfo Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

getSafeGetGeneric :: forall a. SafeCopy' a => StateT (Map TypeRep Int32) Get (Get a) Source #

Whereas the other getSafeGet is only run when we know we need a version, this one is run for every field and must decide whether to read a version or not. It constructs a Map TypeRep Int32 and reads whent he new TypeRep is not in the map.

getSafePutGeneric :: forall a. SafeCopy' a => (a -> Contained Put) -> a -> RWST () [Put] (Set TypeRep) PutM () Source #

This version returns (Put, Put), the collected version tags and the collected serialized fields. The original getSafePut result type prevents doing this because each fields may have a different type. Maybe you can show me a better way

safePutGeneric :: forall a. GSafeCopy a => a -> Put Source #

Generic only version of safePut. Instead of calling putCopy it calls putCopyDefault, a copy of the implementation of the SafeCopy default method for putCopy.

putCopyDefault :: forall a. GSafeCopy a => a -> Contained Put Source #

See safePutGeneric. A copy of the code in the default implementation of the putCopy method.

safeGet :: SafeCopy a => Get a Source #

Parse a version tagged data type and then migrate it to the desired type. Any serialized value has been extended by the return type can be parsed.

getSafeGet :: forall a. SafeCopy a => Get (Get a) Source #

Parse a version tag and return the corresponding migrated parser. This is useful when you can prove that multiple values have the same version. See getSafePut.

safePut :: SafeCopy a => a -> Put Source #

Serialize a data type by first writing out its version tag. This is much simpler than the corresponding safeGet since previous versions don't come into play.

getSafePut :: forall a. SafeCopy a => PutM (a -> Put) Source #

Serialize the version tag and return the associated putter. This is useful when serializing multiple values with the same version. See getSafeGet.

extended_extension :: (Migrate a, Migrate (Reverse a)) => Kind a Source #

The extended_extension kind lets the system know that there is at least one previous and one future version of this type.

extended_base :: Migrate (Reverse a) => Kind a Source #

The extended_base kind lets the system know that there is at least one future version of this type.

extension :: Migrate a => Kind a Source #

The extension kind lets the system know that there is at least one previous version of this type. A given data type can only extend a single other data type. However, it is perfectly fine to build chains of extensions. The migrations between each step is handled automatically.

base :: Kind a Source #

The default kind. Does not extend any type.

primitive :: Kind a Source #

Primitive kinds aren't version tagged. This kind is used for small or built-in types that won't change such as Int or Bool.

newtype Version a Source #

A simple numeric version id.

Constructors

Version 

Fields

Instances
Eq (Version a) Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

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

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

Num (Version a) Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

(+) :: Version a -> Version a -> Version a #

(-) :: Version a -> Version a -> Version a #

(*) :: Version a -> Version a -> Version a #

negate :: Version a -> Version a #

abs :: Version a -> Version a #

signum :: Version a -> Version a #

fromInteger :: Integer -> Version a #

Read (Version a) Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Show (Version a) Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

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

show :: Version a -> String #

showList :: [Version a] -> ShowS #

Serialize (Version a) Source # 
Instance details

Defined in Data.SafeCopy.SafeCopy

Methods

put :: Putter (Version a) #

get :: Get (Version a) #

newtype Contained a Source #

To ensure that no-one reads or writes values without handling versions correct, it is necessary to restrict access to getCopy and putCopy. This is where Contained enters the picture. It allows you to put values in to a container but not to take them out again.

Constructors

Contained 

Fields

contain :: a -> Contained a Source #

Place a value in an unbreakable container.

checkConsistency :: (SafeCopy a, MonadFail m) => Proxy a -> m b -> m b Source #

unpureCheckConsistency :: SafeCopy a => Proxy a -> b -> b Source #

PutM doesn't have reasonable fail implementation. It just throws unpure exception anyway.

data Proxy a Source #

Constructors

Proxy 

mkProxy :: a -> Proxy a Source #

asProxyType :: a -> Proxy a -> a Source #

deriveSafeCopy :: Version a -> Name -> Name -> Q [Dec] Source #

Derive an instance of SafeCopy.

When serializing, we put a Word8 describing the constructor (if the data type has more than one constructor). For each type used in the constructor, we call getSafePut (which immediately serializes the version of the type). Then, for each field in the constructor, we use one of the put functions obtained in the last step.

For example, given the data type and the declaration below

data T0 b = T0 b Int
deriveSafeCopy 1 'base ''T0
   

we generate

instance (SafeCopy a, SafeCopy b) =>
         SafeCopy (T0 b) where
    putCopy (T0 arg1 arg2) = contain $ do put_b   <- getSafePut
                                          put_Int <- getSafePut
                                          put_b   arg1
                                          put_Int arg2
                                          return ()
    getCopy = contain $ do get_b   <- getSafeGet
                           get_Int <- getSafeGet
                           return T0 <*> get_b <*> get_Int
    version = 1
    kind = base
   

And, should we create another data type as a newer version of T0, such as

data T a b = C a a | D b Int
deriveSafeCopy 2 'extension ''T

instance SafeCopy b => Migrate (T a b) where
  type MigrateFrom (T a b) = T0 b
  migrate (T0 b i) = D b i
   

we generate

instance (SafeCopy a, SafeCopy b) =>
         SafeCopy (T a b) where
    putCopy (C arg1 arg2) = contain $ do putWord8 0
                                         put_a <- getSafePut
                                         put_a arg1
                                         put_a arg2
                                         return ()
    putCopy (D arg1 arg2) = contain $ do putWord8 1
                                         put_b   <- getSafePut
                                         put_Int <- getSafePut
                                         put_b   arg1
                                         put_Int arg2
                                         return ()
    getCopy = contain $ do tag <- getWord8
                           case tag of
                             0 -> do get_a <- getSafeGet
                                     return C <*> get_a <*> get_a
                             1 -> do get_b   <- getSafeGet
                                     get_Int <- getSafeGet
                                     return D <*> get_b <*> get_Int
                             _ -> fail $ "Could not identify tag \"" ++
                                         show tag ++ "\" for type Main.T " ++
                                         "that has only 2 constructors.  " ++
                                         "Maybe your data is corrupted?"
    version = 2
    kind = extension
   

Note that by using getSafePut, we saved 4 bytes in the case of the C constructor. For D and T0, we didn't save anything. The instance derived by this function always use at most the same space as those generated by deriveSafeCopySimple, but never more (as we don't call 'getSafePut'/'getSafeGet' for types that aren't needed).

Note that you may use deriveSafeCopySimple with one version of your data type and deriveSafeCopy in another version without any problems.

deriveSafeCopySimple :: Version a -> Name -> Name -> Q [Dec] Source #

Derive an instance of SafeCopy. The instance derived by this function is simpler than the one derived by deriveSafeCopy in that we always use safePut and safeGet (instead of getSafePut and getSafeGet).

When serializing, we put a Word8 describing the constructor (if the data type has more than one constructor) and, for each field of the constructor, we use safePut.

For example, given the data type and the declaration below

data T a b = C a a | D b Int
deriveSafeCopySimple 1 'base ''T
   

we generate

instance (SafeCopy a, SafeCopy b) =>
         SafeCopy (T a b) where
    putCopy (C arg1 arg2) = contain $ do putWord8 0
                                         safePut arg1
                                         safePut arg2
                                         return ()
    putCopy (D arg1 arg2) = contain $ do putWord8 1
                                         safePut arg1
                                         safePut arg2
                                         return ()
    getCopy = contain $ do tag <- getWord8
                           case tag of
                             0 -> do return C <*> safeGet <*> safeGet
                             1 -> do return D <*> safeGet <*> safeGet
                             _ -> fail $ "Could not identify tag \"" ++
                                         show tag ++ "\" for type Main.T " ++
                                         "that has only 2 constructors.  " ++
                                         "Maybe your data is corrupted?"
    version = 1
    kind = base
   

Using this simpler instance means that you may spend more bytes when serializing data. On the other hand, it is more straightforward and may match any other format you used in the past.

Note that you may use deriveSafeCopy with one version of your data type and deriveSafeCopySimple in another version without any problems.

deriveSafeCopyHappstackData :: Version a -> Name -> Name -> Q [Dec] Source #

Derive an instance of SafeCopy. The instance derived by this function should be compatible with the instance derived by the module Happstack.Data.SerializeTH of the happstack-data package. The instances use only safePut and safeGet (as do the instances created by deriveSafeCopySimple), but we also always write a Word8 tag, even if the data type isn't a sum type.

For example, given the data type and the declaration below

data T0 b = T0 b Int
deriveSafeCopy 1 'base ''T0
   

we generate

instance (SafeCopy a, SafeCopy b) =>
         SafeCopy (T0 b) where
    putCopy (T0 arg1 arg2) = contain $ do putWord8 0
                                          safePut arg1
                                          safePut arg2
                                          return ()
    getCopy = contain $ do tag <- getWord8
                           case tag of
                             0 -> do return T0 <*> safeGet <*> safeGet
                             _ -> fail $ "Could not identify tag \"" ++
                                         show tag ++ "\" for type Main.T0 " ++
                                         "that has only 1 constructors.  " ++
                                         "Maybe your data is corrupted?"
    version = 1
    kind = base
   

This instance always consumes at least the same space as deriveSafeCopy or deriveSafeCopySimple, but may use more because of the useless tag. So we recomend using it only if you really need to read a previous version in this format, and not for newer versions.

Note that you may use deriveSafeCopy with one version of your data type and deriveSafeCopyHappstackData in another version without any problems.

followSynonyms :: Type -> Q Type Source #

Follow type synonyms. This allows us to see, for example, that [Char] and String are the same type and we just need to call getSafePut or getSafeGet once for both.