2 {-# LANGUAGE Rank2Types #-}
3 {-# LANGUAGE TypeOperators #-}
4 {-# OPTIONS_GHC -fno-warn-missing-methods #-}
6 module Language.Symantic.Lib.Data.Peano where
8 import Data.Type.Equality ((:~:)(Refl))
10 -- * Types 'Zero' and 'Succ'
11 -- | Type-level peano numbers of kind '*'.
13 -- | Undefined instance required to build errors.
15 -- | Undefined instance required to build errors.
18 -- | Undefined instance required to build errors.
20 -- | Undefined instance required to build errors.
24 -- | Singleton for peano numbers.
27 SSucc :: SPeano p -> SPeano (Succ p)
29 integral_from_peano :: Integral i => SPeano p -> i
30 integral_from_peano SZero = 0
31 integral_from_peano (SSucc x) = 1 + integral_from_peano x
33 peano_from_integral :: Integral i => i -> (forall p. SPeano p -> ret) -> ret
34 peano_from_integral 0 k = k SZero
35 peano_from_integral i k | i > 0 =
36 peano_from_integral (i - 1) $ \p -> k (SSucc p)
37 peano_from_integral _ _ = error "peano_from_integral"
39 peano_eq :: forall x y. SPeano x -> SPeano y -> Maybe (x :~: y)
40 peano_eq SZero SZero = Just Refl
41 peano_eq (SSucc x) (SSucc y)
42 | Just Refl <- x `peano_eq` y
44 peano_eq _ _ = Nothing