Safe Haskell | None |
---|---|
Language | Haskell2010 |
This is a mess, sorry. This code was extracted from another project.
Currently changelog
is the most useful function here – see its
description for an example.
Synopsis
- deriveSafeCopySorted :: Version a -> Name -> Name -> Q [Dec]
- data Change
- changelog :: Name -> (TypeVersion, TypeVersion) -> [Change] -> DecsQ
- hs :: QuasiQuoter
- data GenConstructor
- genVer :: Name -> Int -> [GenConstructor] -> Q [Dec]
- data MigrateConstructor
- migrateVer :: Name -> Int -> [MigrateConstructor] -> Q Exp
- data TypeVersion
Migration for records
deriveSafeCopySorted :: Version a -> Name -> Name -> Q [Dec] Source #
Sorts fields (but not constructors), uses Simple
encoding, only works
on records.
A change from one version of a record (one constructor, several fields) to
another version. We only record the latest version, so we have to be able to
reconstruct the previous version knowing the current version and a list of
Change
s.
:: Name | Type (without version suffix) |
-> (TypeVersion, TypeVersion) | New version, old version |
-> [Change] | List of changes between this version and previous one |
-> DecsQ |
Generate previous version of the type.
Assume that the new type and the changelog are, respectively:
-- version 4 data Foo = FooRec { b :: Bool, c :: Int } changelog ''Foo (Current 4, Past 3) [ Removed "a" [t|String|], Added "c" [|if null a then 0 else 1|] ]
Then we will generate a type called Foo_v3:
data Foo_v3 = FooRec_v3 { a_v3 :: String, b_v3 :: Bool }
We'll also generate a migration instance:
instance Migrate Foo where type MigrateFrom Foo = Foo_v3 migrate old = FooRec { b = b_v3 old, c = if null (a_v3 old) then 0 else 1 }
Note that you must use deriveSafeCopySorted
for types that use changelog
because otherwise fields will be parsed in the wrong order. Specifically,
imagine that you have created a type with fields “b” and “a” and then removed
“b”. changelog
has no way of knowing from “the current version has field
“a”” and “the previous version also had field “b”” that the previous version
had fields “b, a” and not “a, b”. Usual deriveSafeCopy
or
deriveSafeCopySimple
care about field order and thus will treat “b, a” and
“a, b” as different types.
hs :: QuasiQuoter Source #
Migration for constructors
data GenConstructor Source #
A type for specifying what constructors existed in an old version of a sum datatype.
:: Name | Name of type to generate old version for |
-> Int | Version to generate |
-> [GenConstructor] | List of constructors in the version we're generating |
-> Q [Dec] |
Generate an old version of a sum type (used for SafeCopy
).
data MigrateConstructor Source #
A type for migrating constructors from an old version of a sum datatype.
:: Name | Type we're migrating to |
-> Int | Version we're migrating from |
-> [MigrateConstructor] | For each constructor existing in the (old version of) type, a specification of how to migrate it. |
-> Q Exp |
Generate SafeCopy
migration code for a sum datatype.
Utilities
data TypeVersion Source #
An ADT for versions. Only used in invocations of changelog
.
Instances
Show TypeVersion Source # | |
Defined in Data.SafeCopy.Migrate showsPrec :: Int -> TypeVersion -> ShowS # show :: TypeVersion -> String # showList :: [TypeVersion] -> ShowS # |