Skip to content

Instantly share code, notes, and snippets.

@esoeylemez
Created April 26, 2018 11:10
Show Gist options
  • Save esoeylemez/cb2b0e54815d2770a97a287d14a599c1 to your computer and use it in GitHub Desktop.
Save esoeylemez/cb2b0e54815d2770a97a287d14a599c1 to your computer and use it in GitHub Desktop.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
import Data.Functor.Const
import Data.Functor.Identity
data Nat = Z | S Nat
type V0 = 'Z
type V1 = 'S V0
type V2 = 'S V1
type V3 = 'S V2
type family Since (c :: Nat) (v :: Nat) :: * -> * where
Since 'Z v = Identity
Since c 'Z = Const ()
Since ('S c) ('S v) = Since c v
data Person (v :: Nat) =
Person {
personName :: Since V0 v String,
personAge :: Since V1 v Integer,
personLocation :: Since V2 v String
}
deriving instance Show (Person V0)
deriving instance Show (Person V1)
deriving instance Show (Person V2)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment