th-typegraph-1.0.2: Graph of the subtype relation

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.TypeGraph.SafeCopyDerive

Synopsis

Documentation

unVersion :: Version a -> Int32 Source #

FIXME - Bogus reimplementation of the hidden Data.SafeCopy.unVersion function

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.