versioning-0.3.1.0: Type-safe data versioning.

Safe HaskellNone
LanguageHaskell2010

Versioning.Base

Contents

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

Types

data V Source #

The version of a data model

Constructors

VZero 
VSucc V 
Instances
Eq V Source # 
Instance details

Defined in Versioning.Base

Methods

(==) :: V -> V -> Bool #

(/=) :: V -> V -> Bool #

Show V Source # 
Instance details

Defined in Versioning.Base

Methods

showsPrec :: Int -> V -> ShowS #

show :: V -> String #

showList :: [V] -> ShowS #

type family VPred (v :: V) :: V where ... Source #

Get the previous version

Equations

VPred (VSucc v) = v 
VPred VZero = VZero 

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

Get the type-level natural of a version

Equations

VNat v = VNat' v 0 

type family VCmp (v :: V) (w :: V) :: Ordering where ... Source #

Compare two versions

Equations

VCmp VZero VZero = EQ 
VCmp VZero v = LT 
VCmp v VZero = GT 
VCmp (VSucc v) (VSucc w) = VCmp v w 

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 s v a = Since' (VCmp s v) a NA 

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

Same as Since, for sum types. The only difference between Since and SinceS is in the type used to indicate absence. In Since absence is expressed with NA, which is isomorphic to '()'. In SinceS it is expressed with Bare, which is isomorphic to Void.

Equations

SinceS s v a = Since' (VCmp s v) a Bare 

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 u v a = Until' (VCmp u v) a NA 

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

Same as Until, for sum types.

Equations

UntilS u v a = Until' (VCmp u v) a Bare 

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 V0 = VZero Source #

type V1 = VSucc V0 Source #

type V2 = VSucc V1 Source #

type V3 = VSucc V2 Source #

type V4 = VSucc V3 Source #

type V5 = VSucc V4 Source #

type V6 = VSucc V5 Source #

type V7 = VSucc V6 Source #

type V8 = VSucc V7 Source #

type V9 = VSucc V8 Source #

Functions

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

Get the version number of a versioned value