fin-0.0.1: Nat and Fin: peano naturals and finite numbers

Safe HaskellNone
LanguageHaskell2010

Data.Type.Nat

Contents

Description

Nat numbers. DataKinds stuff.

This module re-exports Data.Nat, and adds type-level things.

Synopsis

Natural, Nat numbers

data Nat Source #

Nat natural numbers.

Better than GHC's built-in Nat for some use cases.

Constructors

Z 
S Nat 

Instances

Enum Nat Source # 

Methods

succ :: Nat -> Nat #

pred :: Nat -> Nat #

toEnum :: Int -> Nat #

fromEnum :: Nat -> Int #

enumFrom :: Nat -> [Nat] #

enumFromThen :: Nat -> Nat -> [Nat] #

enumFromTo :: Nat -> Nat -> [Nat] #

enumFromThenTo :: Nat -> Nat -> Nat -> [Nat] #

Eq Nat Source # 

Methods

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

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

Integral Nat Source # 

Methods

quot :: Nat -> Nat -> Nat #

rem :: Nat -> Nat -> Nat #

div :: Nat -> Nat -> Nat #

mod :: Nat -> Nat -> Nat #

quotRem :: Nat -> Nat -> (Nat, Nat) #

divMod :: Nat -> Nat -> (Nat, Nat) #

toInteger :: Nat -> Integer #

Data Nat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Nat -> c Nat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Nat #

toConstr :: Nat -> Constr #

dataTypeOf :: Nat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Nat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Nat) #

gmapT :: (forall b. Data b => b -> b) -> Nat -> Nat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nat -> r #

gmapQ :: (forall d. Data d => d -> u) -> Nat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Nat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Nat -> m Nat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Nat -> m Nat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Nat -> m Nat #

Num Nat Source # 

Methods

(+) :: Nat -> Nat -> Nat #

(-) :: Nat -> Nat -> Nat #

(*) :: Nat -> Nat -> Nat #

negate :: Nat -> Nat #

abs :: Nat -> Nat #

signum :: Nat -> Nat #

fromInteger :: Integer -> Nat #

Ord Nat Source # 

Methods

compare :: Nat -> Nat -> Ordering #

(<) :: Nat -> Nat -> Bool #

(<=) :: Nat -> Nat -> Bool #

(>) :: Nat -> Nat -> Bool #

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

max :: Nat -> Nat -> Nat #

min :: Nat -> Nat -> Nat #

Real Nat Source # 

Methods

toRational :: Nat -> Rational #

Show Nat Source #

Nat is printed as Natural.

To see explicit structure, use explicitShow or explicitShowsPrec

Methods

showsPrec :: Int -> Nat -> ShowS #

show :: Nat -> String #

showList :: [Nat] -> ShowS #

NFData Nat Source # 

Methods

rnf :: Nat -> () #

Hashable Nat Source # 

Methods

hashWithSalt :: Int -> Nat -> Int #

hash :: Nat -> Int #

TestEquality Nat SNat # 

Methods

testEquality :: f a -> f b -> Maybe ((SNat :~: a) b) #

type (==) Nat n m # 
type (==) Nat n m = EqNat n m

toNatural :: Nat -> Natural Source #

Convert Nat to Natural

>>> toNatural 0
0
>>> toNatural 2
2
>>> toNatural $ S $ S $ Z
2

fromNatural :: Natural -> Nat Source #

Convert Natural to Nat

>>> fromNatural 4
4
>>> explicitShow (fromNatural 4)
"S (S (S (S Z)))"

cata :: a -> (a -> a) -> Nat -> a Source #

Fold Nat.

>>> cata [] ('x' :) 2
"xx"

Showing

explicitShow :: Nat -> String Source #

show displaying a structure of Nat.

>>> explicitShow 0
"Z"
>>> explicitShow 2
"S (S Z)"

explicitShowsPrec :: Int -> Nat -> ShowS Source #

showsPrec displaying a structure of Nat.

Singleton

data SNat (n :: Nat) where Source #

Singleton of Nat.

Constructors

SZ :: SNat Z 
SS :: SNatI n => SNat (S n) 

Instances

TestEquality Nat SNat Source # 

Methods

testEquality :: f a -> f b -> Maybe ((SNat :~: a) b) #

Show (SNat p) Source # 

Methods

showsPrec :: Int -> SNat p -> ShowS #

show :: SNat p -> String #

showList :: [SNat p] -> ShowS #

snatToNat :: forall n. SNat n -> Nat Source #

Convert SNat to Nat.

>>> snatToNat (snat :: SNat Nat1)
1

snatToNatural :: forall n. SNat n -> Natural Source #

Convert SNat to Natural

>>> snatToNatural (snat :: SNat Nat0)
0
>>> snatToNatural (snat :: SNat Nat2)
2

Implicit

class SNatI (n :: Nat) where Source #

Convenience class to get SNat.

Minimal complete definition

snat

Methods

snat :: SNat n Source #

Instances

SNatI Z Source # 

Methods

snat :: SNat Z Source #

SNatI n => SNatI (S n) Source # 

Methods

snat :: SNat (S n) Source #

reify :: forall r. Nat -> (forall n. SNatI n => Proxy n -> r) -> r Source #

Reify Nat.

>>> reify nat3 reflect
3

reflect :: forall n proxy. SNatI n => proxy n -> Nat Source #

Reflect type-level Nat to the term level.

reflectToNum :: forall n m proxy. (SNatI n, Num m) => proxy n -> m Source #

As reflect but with any Num.

Equality

eqNat :: forall n m. (SNatI n, SNatI m) => Maybe (n :~: m) Source #

Decide equality of type-level numbers.

>>> eqNat :: Maybe (Nat3 :~: Plus Nat1 Nat2)
Just Refl
>>> eqNat :: Maybe (Nat3 :~: Mult Nat2 Nat2)
Nothing

type family EqNat (n :: Nat) (m :: Nat) where ... Source #

Type family used to implement == from Data.Type.Equality module.

Equations

EqNat Z Z = True 
EqNat (S n) (S m) = EqNat n m 
EqNat n m = False 

Induction

induction Source #

Arguments

:: SNatI n 
=> f Z

zero case

-> (forall m. SNatI m => f m -> f (S m))

induction step

-> f n 

Induction on Nat.

Useful in proofs or with GADTs, see source of proofPlusNZero.

induction1 Source #

Arguments

:: SNatI n 
=> f Z a

zero case

-> (forall m. SNatI m => f m a -> f (S m) a)

induction step

-> f n a 

Induction on Nat, functor form. Useful for computation.

>>> induction1 (Tagged 0) $ retagMap (+2) :: Tagged Nat3 Int
Tagged 6

class SNatI n => InlineInduction (n :: Nat) where Source #

The induction will be fully inlined.

See test/Inspection.hs.

Minimal complete definition

inlineInduction1

Methods

inlineInduction1 :: f Z a -> (forall m. InlineInduction m => f m a -> f (S m) a) -> f n a Source #

Instances

InlineInduction Z Source # 

Methods

inlineInduction1 :: f Z a -> (forall (m :: Nat). InlineInduction m => f m a -> f (S m) a) -> f Z a Source #

InlineInduction n => InlineInduction (S n) Source # 

Methods

inlineInduction1 :: f Z a -> (forall (m :: Nat). InlineInduction m => f m a -> f (S m) a) -> f (S n) a Source #

inlineInduction Source #

Arguments

:: InlineInduction n 
=> f Z

zero case

-> (forall m. InlineInduction m => f m -> f (S m))

induction step

-> f n 

Example: unfoldedFix

unfoldedFix :: forall n a proxy. InlineInduction n => proxy n -> (a -> a) -> a Source #

Unfold n steps of a general recursion.

Note: Always benchmark. This function may give you both bad properties: a lot of code (increased binary size), and worse performance.

For known n unfoldedFix will unfold recursion, for example

unfoldedFix (Proxy :: Proxy Nat3) f = f (f (f (fix f)))

Arithmetic

type family Plus (n :: Nat) (m :: Nat) :: Nat where ... Source #

Addition.

>>> reflect (snat :: SNat (Plus Nat1 Nat2))
3

Equations

Plus Z m = m 
Plus (S n) m = S (Plus n m) 

type family Mult (n :: Nat) (m :: Nat) :: Nat where ... Source #

Multiplication.

>>> reflect (snat :: SNat (Mult Nat2 Nat3))
6

Equations

Mult Z m = Z 
Mult (S n) m = Plus m (Mult n m) 

Conversion to GHC Nat

type family ToGHC (n :: Nat) :: Nat where ... Source #

Convert to GHC Nat.

>>> :kind! ToGHC Nat5
ToGHC Nat5 :: GHC.Nat
= 5

Equations

ToGHC Z = 0 
ToGHC (S n) = 1 + ToGHC n 

type family FromGHC (n :: Nat) :: Nat where ... Source #

Convert from GHC Nat.

>>> :kind! FromGHC 7
FromGHC 7 :: Nat
= 'S ('S ('S ('S ('S ('S ('S 'Z))))))

Equations

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

Aliases

Nat

promoted Nat

type Nat0 = Z Source #

type Nat1 = S Nat0 Source #

type Nat2 = S Nat1 Source #

type Nat3 = S Nat2 Source #

type Nat4 = S Nat3 Source #

type Nat5 = S Nat4 Source #

type Nat6 = S Nat5 Source #

type Nat7 = S Nat6 Source #

type Nat8 = S Nat7 Source #

type Nat9 = S Nat8 Source #

Proofs

proofPlusNZero :: SNatI n => Plus n Nat0 :~: n Source #

n + 0 = n

proofMultNZero :: forall n proxy. SNatI n => proxy n -> Mult n Nat0 :~: Nat0 Source #

n * 0 = n

proofMultOneN :: SNatI n => Mult Nat1 n :~: n Source #

1 * n = n

proofMultNOne :: SNatI n => Mult n Nat1 :~: n Source #

n * 1 = n