Skip to content

Instantly share code, notes, and snippets.

@alexpeits
Last active September 5, 2018 20:04
Show Gist options
  • Save alexpeits/74028b1b93d9544fb3a3b99cbe6848f6 to your computer and use it in GitHub Desktop.
Save alexpeits/74028b1b93d9544fb3a3b99cbe6848f6 to your computer and use it in GitHub Desktop.
Haskell Peano Arithmetic
{-# LANGUAGE GADTs #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Eliminate where
data Nat = Zero | Succ Nat | Pred Nat
type family n + m where
Zero + m = E m
Succ n + m = Succ (E n + E m)
Pred n + m = Pred (E n + E m)
type family E n where
E (Succ (Pred n)) = E n
E (Pred (Succ n)) = E n
E (Succ n) = Succ (E n)
E (Pred n) = Pred (E n)
E Zero = Zero
data Vec :: (* -> Nat -> *) where
VNil :: Vec a Zero
(:>) :: a -> Vec a n -> Vec a (Succ n)
(+++) :: Vec a n -> Vec a m -> Vec a (n + m)
VNil +++ ys = ys
(x :> xs) +++ ys = x :> (xs +++ ys)
• Could not deduce: E m ~ m
from the context: n ~ 'Zero
bound by a pattern with constructor: VNil :: forall a. Vec a 'Zero,
in an equation for ‘+++’
at Eliminate.hs:27:1-4
‘m’ is a rigid type variable bound by
the type signature for:
(+++) :: forall a (n :: Nat) (m :: Nat).
Vec a n -> Vec a m -> Vec a (n + m)
at Eliminate.hs:26:1-44
Expected type: Vec a (n + m)
Actual type: Vec a m
• In the expression: ys
In an equation for ‘+++’: VNil +++ ys = ys
• Relevant bindings include
ys :: Vec a m
(bound at Eliminate.hs:27:15)
(+++) :: Vec a n -> Vec a m -> Vec a (n + m)
(bound at Eliminate.hs:27:11)
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Peano where
data Nat = Zero | Succ Nat
type family n + m where
Zero + m = m
Succ n + m = Succ (n + m)
type family n * m where
Zero * m = Zero
Succ n * m = m + (n * m)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment