versioning-0.2.0.0: Type-safe data versioning.

Safe HaskellNone
LanguageHaskell2010

Versioning.Base

Description

This module provides some tools to encode multiple versions of a data model in a single data-type parametrized by version number. The addition or removal of a field can be expressed through the Since and Until type families.

Example:

data Rec v = Rec
    { foo :: Int               -- this field exists in all versions
    , bar :: Since V2 v Bool   -- this field has been introduced in V2
    , baz :: Until V2 v Double -- this field has been removed in V3
    }

Besides reducing the number of data declarations, this approach also has other advantages:

  • It makes migrations declarative and self-documenting.
  • It allows for less verbose version-upcasting functions, since the fields that have a non-parametric type do not need to be copied.
  • It is a foundation on which other useful abstractions can be built.

Please note that some classes may require a separate standalone deriving clause for each version of a data-type or some kind of inductive deriving mechanism.

Synopsis

Documentation

newtype V Source #

The version of a data model

Constructors

V Nat 

type family GetV (v :: V) :: Nat where ... Source #

Get the type-level natural of a version

Equations

GetV (V n) = n 

versionNumber :: forall a v. KnownNat (GetV v) => a v -> Natural Source #

Get the version number of a versioned value

type family Since (s :: V) (v :: V) a :: * where ... Source #

This allows us to express that a field is only present since a given version. The first parameter is the version in which the field has been introduced, the second parameter is the actual version of the data-type.

Equations

Since (V 1) (V v) a = a 
Since (V s) (V 1) a = NA 
Since (V s) (V v) a = Since (V (s - 1)) (V (v - 1)) a 

type family Until (u :: V) (v :: V) a :: * where ... Source #

This allows us to express that a field is only present until a given version. The first parameter is the last version in which the field is present, the second parameter is the actual version of the data-type.

Equations

Until (V u) (V 1) a = a 
Until (V 1) (V v) a = NA 
Until (V u) (V v) a = Until (V (u - 1)) (V (v - 1)) a 

type NA = Maybe Bare Source #

A type indicating absence. The Maybe is a hack needed to let aeson parse a record successfully even if a field of type NA is missing.

Ideally we would like to define it as

data NA = NA

but this would not work with FromJSON instances that are derived with Generic.

na :: NA Source #

A placeholder for an absent value.

type V1 = V 1 Source #

type V2 = V 2 Source #

type V3 = V 3 Source #

type V4 = V 4 Source #

type V5 = V 5 Source #

type V6 = V 6 Source #

type V7 = V 7 Source #

type V8 = V 8 Source #

type V9 = V 9 Source #

type V10 = V 10 Source #

type V11 = V 11 Source #

type V12 = V 12 Source #

type V13 = V 13 Source #

type V14 = V 14 Source #

type V15 = V 15 Source #

type V16 = V 16 Source #

type V17 = V 17 Source #

type V18 = V 18 Source #

type V19 = V 19 Source #

type V20 = V 20 Source #