Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- data Nat
- toNatural :: Nat -> Natural
- fromNatural :: Natural -> Nat
- cata :: a -> (a -> a) -> Nat -> a
- explicitShow :: Nat -> String
- explicitShowsPrec :: Int -> Nat -> ShowS
- data SNat n where
- snatToNat :: forall n. SNat n -> Nat
- snatToNatural :: forall n. SNat n -> Natural
- class SNatI n where
- reify :: forall r. Nat -> (forall n. SNatI n => Proxy n -> r) -> r
- reflect :: forall n proxy. SNatI n => proxy n -> Nat
- reflectToNum :: forall n m proxy. (SNatI n, Num m) => proxy n -> m
- induction :: forall n f. SNatI n => f Z -> (forall m. SNatI m => f m -> f (S m)) -> f n
- induction1 :: forall n f a. SNatI n => f Z a -> (forall m. SNatI m => f m a -> f (S m) a) -> f n a
- class SNatI n => InlineInduction n where
- inlineInduction :: forall n f. InlineInduction n => f Z -> (forall m. SNatI m => f m -> f (S m)) -> f n
- type family Plus (n :: Nat) (m :: Nat) :: Nat where ...
- type family Mult (n :: Nat) (m :: Nat) :: Nat where ...
- zero :: Nat
- one :: Nat
- two :: Nat
- three :: Nat
- four :: Nat
- five :: Nat
- type Zero = Z
- type One = S Zero
- type Two = S One
- type Three = S Two
- type Four = S Three
- type Five = S Four
- proofPlusZeroN :: Plus Zero n :~: n
- proofPlusNZero :: SNatI n => Plus n Zero :~: n
- proofMultZeroN :: Mult Zero n :~: Zero
- proofMultNZero :: forall n. SNatI n => Proxy n -> Mult n Zero :~: Zero
- proofMultOneN :: SNatI n => Mult One n :~: n
- proofMultNOne :: SNatI n => Mult n One :~: n
Natural, Nat numbers
Nat natural numbers.
Better than GHC's built-in Nat
for some use cases.
fromNatural :: Natural -> Nat Source #
Showing
explicitShow :: Nat -> String Source #
Singleton
Singleton of Nat
.
snatToNatural :: forall n. SNat n -> Natural Source #
Implicit
Convenience class to get SNat
.
reify :: forall r. Nat -> (forall n. SNatI n => Proxy n -> r) -> r Source #
Reify Nat
.
>>>
reify three 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 #
Induction
Induction on Nat
.
Useful in proofs or with GADTs, see source of proofPlusNZero
.
Induction on Nat
, functor form. Useful for computation.
>>>
induction1 (Tagged 0) $ retagMap (+2) :: Tagged Three Int
Tagged 6
class SNatI n => InlineInduction n where Source #
The induction will be fully inlined.
See test/Inspection.hs
.
InlineInduction Z Source # | |
InlineInduction n => InlineInduction (S n) Source # | |
:: InlineInduction n | |
=> f Z | zero case |
-> (forall m. SNatI m => f m -> f (S m)) | induction step |
-> f n |
See InlineInduction
.
Arithmetic
type family Plus (n :: Nat) (m :: Nat) :: Nat where ... Source #
Addition.
>>>
reflect (snat :: SNat (Plus One Two))
3
type family Mult (n :: Nat) (m :: Nat) :: Nat where ... Source #
Multiplication.
>>>
reflect (snat :: SNat (Mult Two Three))
6