Haskell was unable to combine instance instance equations

I am trying to mark the canonical Nat data type with (even / odd) parity to see if we can get any free theorems. Here is the code:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}

-- Use DataKind promotion with type function for even-odd

module EvenOdd where

  data Parity = Even | Odd
  -- Parity is promoted to kind level Parity.
  -- Even & Odd to type level 'Even & 'Odd of kind Parity

  -- We define type-function opp to establish the relation that
  -- type 'Even is opposite of 'Odd, and vice-versa
  type family Opp (n :: Parity) :: Parity
  type instance Opp 'Even = 'Odd
  type instance Opp 'Odd = 'Even

 -- We tag natural number with the type of its parity
  data Nat :: Parity -> * where
     Zero :: Nat 'Even
     Succ :: Nat p -> Nat (Opp p)

  -- Now we (should) get free theorems.
  -- 1. Plus of two even numbers is even
  evenPlus :: Nat 'Even -> Nat 'Even -> Nat 'Even
  evenPlus Zero n2 = n2  -- Line 31
  evenPlus (Succ (Succ n1)) n2 = Succ (Succ (evenPlus n1 n2))

However, the GHC throws an error like:

Could not deduce (p1 ~ 'Even)
from the context ('Even ~ Opp p)
  bound by a pattern with constructor
             Succ :: forall (p :: Parity). Nat p -> Nat (Opp p),
           in an equation for `evenPlus'
  at even-odd.hs:31:13-26
or from (p ~ Opp p1)
  bound by a pattern with constructor
             Succ :: forall (p :: Parity). Nat p -> Nat (Opp p),
           in an equation for `evenPlus'
  at even-odd.hs:31:19-25
  `p1' is a rigid type variable bound by
       a pattern with constructor
         Succ :: forall (p :: Parity). Nat p -> Nat (Opp p),
       in an equation for `evenPlus'
       at even-odd.hs:31:19
Expected type: Nat 'Even
  Actual type: Nat p
In the first argument of `evenPlus', namely `n1'
In the first argument of `Succ', namely `(evenPlus n1 n2)'

As I understand it, the essence of the aforementioned error is that the GHC could not output (p1 ~ 'Even) when the context has the equation: ((Opp (Opp p1)) ~' Even).

Why is this happening? Is there something wrong with my approach?

+4
source share
1 answer

I don't think GADT pattern matching works like this. You have Opp pa constructor as result type. Therefore, if you write something like

f :: Nat 'Even -> ...
f (Succ n) = ...

, Nat (Opp t) ~ Nat 'Even , , Opp t ~ 'Even. , Opp, .

Nat, :

data Nat :: Parity -> * where
  Zero :: Nat 'Even
  Succ :: Nat (Opp p) -> Nat p

.

, .

() . . , Succ Zero Succ Zero :: Opp p ~ 'Even => Nat p, Nat 'Odd. ok.

, Succ, Opp . Parity Even Odd, , :

data Nat :: Parity -> * where
  Zero :: Nat 'Even
  Succ :: (Opp (Opp p) ~ p) => Nat (Opp p) -> Nat p

Succ Zero Nat 'Odd, .

+7

All Articles