singleton-nats-0.1.0.0: Unary natural numbers relying on the singletons infrastructure.

Safe HaskellNone
LanguageHaskell2010

Data.Nat

Documentation

data Nat Source

Constructors

Z 
S Nat 

Instances

Eq Nat 
Ord Nat 
Show Nat 
SingI Nat Z 
POrd Nat (KProxy Nat) 
SEq Nat (KProxy Nat) 
PEq Nat (KProxy Nat) 
SDecide Nat (KProxy Nat) 
SingI Nat n0 => SingI Nat (S n) 
SingKind Nat (KProxy Nat) 
SuppressUnusedWarnings (Nat -> TyFun Nat Nat -> *) (:*$$) 
SuppressUnusedWarnings (Nat -> TyFun Nat Nat -> *) (:+$$) 
SuppressUnusedWarnings (TyFun Nat (TyFun Nat Nat -> *) -> *) (:*$) 
SuppressUnusedWarnings (TyFun Nat (TyFun Nat Nat -> *) -> *) (:+$) 
SuppressUnusedWarnings (TyFun Nat Nat -> *) SSym0 
data Sing Nat where 
type Compare Nat Z Z = EQ 
type (:==) Nat a0 b0 
type Apply Nat Nat SSym0 l0 = SSym1 l0 
type Compare Nat Z (S rhs0) = LT 
type Apply Nat Nat ((:*$$) l1) l0 
type Apply Nat Nat ((:+$$) l1) l0 
type DemoteRep Nat (KProxy Nat) = Nat 
type Compare Nat (S lhs0) Z = GT 
type Compare Nat (S lhs0) (S rhs0) = ThenCmp EQ (Compare Nat lhs0 rhs0) 
type Apply (TyFun Nat Nat -> *) Nat (:*$) l0 = (:*$$) l0 
type Apply (TyFun Nat Nat -> *) Nat (:+$) l0 = (:+$$) l0 

(+) :: Nat -> Nat -> Nat Source

(*) :: Nat -> Nat -> Nat Source

type SNat z = Sing z Source

type family a :* a :: Nat Source

Equations

Z :* b = ZSym0 
(S a) :* b = Apply (Apply (:+$) b) (Apply (Apply (:*$) a) b) 

data (:*$) l Source

Instances

data l :*$$ l Source

Instances

type family a :+ a :: Nat Source

Equations

Z :+ b = b 
(S a) :+ b = Apply SSym0 (Apply (Apply (:+$) a) b) 

data (:+$) l Source

Instances

data l :+$$ l Source

Instances

data SSym0 l Source

Constructors

forall arg . (KindOf (Apply SSym0 arg) ~ KindOf (SSym1 arg)) => SSym0KindInference 

Instances

type SSym1 t = S t Source

type ZSym0 = Z Source

(%:+) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:+$) t) t) Source

(%:*) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:*$) t) t) Source

type family Lit n Source

Equations

Lit 0 = Z 
Lit n = S (Lit (n - 1)) 

type SLit n = Sing (Lit n) Source