type-unary-0.3.2: Type-level and typed unary natural numbers, inequality proofs, vectors

Copyright(c) Conal Elliott 2009-2012
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell98

TypeUnary.Nat

Contents

Description

Experiment in length-typed vectors

Synopsis

Documentation

Value-typed natural numbers

data Nat :: * -> * where Source #

Constructors

Zero :: Nat Z 
Succ :: IsNat n => Nat n -> Nat (S n) 

Instances

Show (Nat n) Source # 

Methods

showsPrec :: Int -> Nat n -> ShowS #

show :: Nat n -> String #

showList :: [Nat n] -> ShowS #

predN :: Nat (S n) -> Nat n Source #

withIsNat :: (IsNat n => Nat n -> a) -> Nat n -> a Source #

natSucc :: Nat n -> Nat (S n) Source #

natIsNat :: Nat n -> IsNat n => Nat n Source #

natToZ :: Num a => Nat n -> a Source #

Interpret a Nat as a plain number

natEq :: Nat m -> Nat n -> Maybe (m :=: n) Source #

Equality test

natAdd :: Nat m -> Nat n -> Nat (m :+: n) Source #

Sum of naturals

natMul :: forall m n. Nat m -> Nat n -> Nat (m :*: n) Source #

Product of naturals

class IsNat n where Source #

Is n a natural number type?

Minimal complete definition

nat

Methods

nat :: Nat n Source #

Instances

IsNat Z Source # 

Methods

nat :: Nat Z Source #

IsNat n => IsNat (S n) Source # 

Methods

nat :: Nat (S n) Source #

induction :: forall p. p Z => (forall n. IsNat n => Dict (p n) -> Dict (p (S n))) -> forall n. IsNat n => Dict (p n) Source #

Peano's induction principle

class (n :+: Z) ~ n => PlusZero n Source #

Instances

(~) * ((:+:) n Z) n => PlusZero n Source # 

Inequality proofs and indices

data m :<: n where infix 4 Source #

Proof that m < n

Constructors

ZLess :: Z :<: S n 
SLess :: (m :<: n) -> S m :<: S n 

succLim :: (m :<: n) -> m :<: S n Source #

Increase the upper limit in an inequality proof

data Index lim Source #

A number under the given limit, with proof

Constructors

IsNat n => Index (n :<: lim) (Nat n) 

Instances

Eq (Index lim) Source # 

Methods

(==) :: Index lim -> Index lim -> Bool #

(/=) :: Index lim -> Index lim -> Bool #

IsNat n => Num (Index n) Source # 

Methods

(+) :: Index n -> Index n -> Index n #

(-) :: Index n -> Index n -> Index n #

(*) :: Index n -> Index n -> Index n #

negate :: Index n -> Index n #

abs :: Index n -> Index n #

signum :: Index n -> Index n #

fromInteger :: Integer -> Index n #

Show (Index n) Source # 

Methods

showsPrec :: Int -> Index n -> ShowS #

show :: Index n -> String #

showList :: [Index n] -> ShowS #

unIndex :: Num a => Index m -> a Source #

succI :: Index m -> Index (S m) Source #

coerceToIndex :: (Eq i, Show i, Num i, IsNat m) => i -> Index m Source #

Index generation from integer. Can fail dynamically if the integer is too large.