Skip to content

Instantly share code, notes, and snippets.

@zelinskiy
Created March 15, 2017 10:53
Show Gist options
  • Select an option

  • Save zelinskiy/dcefefcdd7d6223e65bf6755c98ea202 to your computer and use it in GitHub Desktop.

Select an option

Save zelinskiy/dcefefcdd7d6223e65bf6755c98ea202 to your computer and use it in GitHub Desktop.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE TypeOperators #-}
data Eql a b where
Refl :: Eql a a
--Нужно для протаскивания Рефла
cong :: Eql a b -> Eql (f a) (f b)
cong Refl = Refl
--Заданы такие типы
data Z
data S n
data SNat n where
Zero :: SNat Z
Succ :: SNat n -> SNat (S n)
--С операцией сложения
type family Add m n
type instance Add Z n = n
type instance Add (S m) n = S (Add m n)
add :: SNat n -> SNat m -> SNat (Add n m)
add Zero m = m
add (Succ n) m = Succ (add n m)
--Доказать, что ноль является левой и правой единицей относительно сложения
-- ∀n. 0 + suc n = suc n
plus_suc :: forall n. SNat n
-> Eql (Add Z (S n)) (S n)
plus_suc Zero = Refl
plus_suc (Succ n) = cong (plus_suc n)
-- ∀n. 0 + n = n
plus_zero :: forall n. SNat n
-> Eql (Add Z n) n
plus_zero Zero = Refl
plus_zero (Succ n) = cong (plus_zero n)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment