module Generics.MultiRec.Eq where
import Generics.MultiRec.Base
class HEq phi f where
heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) ->
phi ix -> f r ix -> f r ix -> Bool
class Eq1 f where
eq1 :: (a -> a -> Bool) -> f a -> f a -> Bool
instance Eq1 [] where
eq1 eq [] [] = True
eq1 eq (x1:xs1) (x2:xs2) = eq x1 x2 && eq1 eq xs1 xs2
eq1 eq _ _ = False
instance Eq1 Maybe where
eq1 eq Nothing Nothing = True
eq1 eq (Just x1) (Just x2) = eq x1 x2
eq1 eq _ _ = False
instance El phi xi => HEq phi (I xi) where
heq eq _ (I x1) (I x2) = eq proof x1 x2
instance Eq a => HEq phi (K a) where
heq eq _ (K x1) (K x2) = x1 == x2
instance HEq phi U where
heq eq _ U U = True
instance (HEq phi f, HEq phi g) => HEq phi (f :+: g) where
heq eq p (L x1) (L x2) = heq eq p x1 x2
heq eq p (R y1) (R y2) = heq eq p y1 y2
heq eq _ _ _ = False
instance (HEq phi f, HEq phi g) => HEq phi (f :*: g) where
heq eq p (x1 :*: y1) (x2 :*: y2) = heq eq p x1 x2 && heq eq p y1 y2
instance (Eq1 f, HEq phi g) => HEq phi (f :.: g) where
heq eq p (D x1) (D x2) = eq1 (heq eq p) x1 x2
instance HEq phi f => HEq phi (f :>: ix) where
heq eq p (Tag x1) (Tag x2) = heq eq p x1 x2
instance (Constructor c, HEq phi f) => HEq phi (C c f) where
heq eq p (C x1) (C x2) = heq eq p x1 x2
eq :: (Fam phi, HEq phi (PF phi)) => phi ix -> ix -> ix -> Bool
eq p x1 x2 = heq (\ p (I0 x1) (I0 x2) -> eq p x1 x2) p (from p x1) (from p x2)