Skip to content

Instantly share code, notes, and snippets.

@mietek
Created November 13, 2016 01:11
Show Gist options
  • Save mietek/e1a644889498d11a383b27897bb6563e to your computer and use it in GitHub Desktop.
Save mietek/e1a644889498d11a383b27897bb6563e to your computer and use it in GitHub Desktop.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE Rank2Types #-}
-- Naturals.
data Nat :: * where
Zero :: Nat
Suc :: Nat -> Nat
instance Eq Nat where
Zero == Zero = True
Suc n == Suc n' = n == n'
_ == _ = False
instance Ord Nat where
Zero <= _ = True
Suc n <= Suc n' = n <= n'
_ <= _ = False
instance Enum Nat where
fromEnum Zero = 0
fromEnum (Suc n) = fromEnum n + 1
toEnum n | n == 0 = Zero
| n > 0 = Suc (toEnum (n - 1))
| otherwise = error "Cannot cast negative Int to Nat"
instance Show Nat where
show = show . fromEnum
-- Singletons for naturals.
data SingNat :: Nat -> * where
SingZero :: SingNat Zero
SingSuc :: forall n. SingNat n -> SingNat (Suc n)
class IsNat (n :: Nat) where
singNat :: SingNat n
instance IsNat Zero where
singNat = SingZero
instance IsNat n => IsNat (Suc n) where
singNat = SingSuc singNat
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment