type-combinators-0.2.0.0: A collection of data types for type-level programming

CopyrightCopyright (C) 2015 Kyle Carter
LicenseBSD3
MaintainerKyle Carter <kylcarte@indiana.edu>
Stabilityexperimental
PortabilityRankNTypes
Safe HaskellNone
LanguageHaskell2010

Type.Family.Nat

Description

Type-level natural numbers, along with frequently used type families over them.

Synopsis

Documentation

data N Source

Constructors

Z 
S N 

Instances

Eq N Source 
Ord N Source 
Show N Source 
TestEquality N Nat 
Read1 N Nat Source 
Read1 N Fin Source 
Show1 N Nat Source 
Show1 N Fin Source 
Ord1 N Nat Source 
Ord1 N Fin Source 
Eq1 N Nat Source 
Eq1 N Fin Source 
Known N Nat Z Source

Z_ is the canonical construction of a Nat Z.

Known N Nat n => Known N Nat (S n) Source

If n is a canonical construction of Nat n, S_ n is the canonical construction of Nat (S n).

(~) N n' (Pred n) => Witness ØC ((~) N (S n') n) (Fin n) Source

A Fin n is a Witness that n >= 1.

That is, Pred n is well defined.

Witness ØC (Known N Nat n) (Nat n) Source

A Nat n is a Witness that there is a canonical construction for Nat n.

Witness ØC (Known N Nat n) (VT k n f a) Source 
type (==) N x y = NatEq x y Source 
type KnownC N Nat Z = ØC 
type KnownC N Nat (S n) = Known N Nat n Source 
type WitnessC ØC ((~) N (S n') n) (Fin n) = (~) N n' (Pred n) Source 
type WitnessC ØC (Known N Nat n) (Nat n) = ØC 
type WitnessC ØC (Known N Nat n) (VT k n f a) = ØC 

type family IsZero x :: Bool Source

Equations

IsZero Z = True 
IsZero (S x) = False 

zeroCong :: (x ~ y) :- (IsZero x ~ IsZero y) Source

zNotS :: (Z ~ S x) :- Fail Source

type family NatEq x y :: Bool Source

Equations

NatEq Z Z = True 
NatEq Z (S y) = False 
NatEq (S x) Z = False 
NatEq (S x) (S y) = NatEq x y 

type family Iota x :: [N] Source

Equations

Iota Z = Ø 
Iota (S x) = x :< Iota x 

iotaCong :: (x ~ y) :- (Iota x ~ Iota y) Source

type family Pred x :: N Source

Equations

Pred (S n) = n 

predCong :: (x ~ y) :- (Pred x ~ Pred y) Source

type family x + y :: N infixr 6 Source

Equations

Z + y = y 
(S x) + y = S (x + y) 

addCong :: (w ~ y, x ~ z) :- ((w + x) ~ (y + z)) Source

type family x * y :: N infixr 7 Source

Equations

Z * y = Z 
(S x) * y = (x * y) + y 

mulCong :: (w ~ y, x ~ z) :- ((w * x) ~ (y * z)) Source

type family x ^ y :: N infixl 8 Source

Equations

x ^ Z = S Z 
x ^ (S y) = (x ^ y) * x 

expCong :: (w ~ y, x ~ z) :- ((w ^ x) ~ (y ^ z)) Source

type family Len as :: N Source

Equations

Len Ø = Z 
Len (a :< as) = S (Len as) 

lenCong :: (as ~ bs) :- (Len as ~ Len bs) Source

type family Ix x as :: k Source

Equations

Ix Z (a :< as) = a 
Ix (S x) (a :< as) = Ix x as 

ixCong :: (x ~ y, as ~ bs) :- (Ix x as ~ Ix y bs) Source

type N0 = Z Source

Convenient aliases for low-value Peano numbers.

type N1 = S N0 Source

type N2 = S N1 Source

type N3 = S N2 Source

type N4 = S N3 Source

type N5 = S N4 Source

type N6 = S N5 Source

type N7 = S N6 Source

type N8 = S N7 Source

type N9 = S N8 Source

type N10 = S N9 Source