{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
module Data.JoinSemilattice.Class.Eq where
import Control.Applicative (liftA2)
import Data.JoinSemilattice.Class.Boolean (BooleanR (..))
import Data.JoinSemilattice.Class.Merge (Merge)
import Data.JoinSemilattice.Defined (Defined (..))
import Data.JoinSemilattice.Intersect (Intersect (..), Intersectable)
import qualified Data.JoinSemilattice.Intersect as Intersect
import Data.Kind (Constraint, Type)
class EqC f x => EqC' f x
instance EqC f x => EqC' f x
class (forall x. EqC' f x => Merge (f x), BooleanR f)
=> EqR (f :: Type -> Type) where
type EqC f :: Type -> Constraint
eqR :: EqC' f x => ( f x, f x, f Bool ) -> ( f x, f x, f Bool )
neR :: (EqR f, EqC' f x) => ( f x, f x, f Bool ) -> ( f x, f x, f Bool )
neR :: (f x, f x, f Bool) -> (f x, f x, f Bool)
neR ( f x
x, f x
y, f Bool
z )
= let ( f Bool
notZ', f Bool
_ ) = (f Bool, f Bool) -> (f Bool, f Bool)
forall (f :: * -> *).
BooleanR f =>
(f Bool, f Bool) -> (f Bool, f Bool)
notR ( f Bool
forall a. Monoid a => a
mempty, f Bool
z )
( f x
x', f x
y', f Bool
notZR ) = (f x, f x, f Bool) -> (f x, f x, f Bool)
forall (f :: * -> *) x.
(EqR f, EqC' f x) =>
(f x, f x, f Bool) -> (f x, f x, f Bool)
eqR ( f x
x, f x
y, f Bool
notZ' )
( f Bool
_, f Bool
z' ) = (f Bool, f Bool) -> (f Bool, f Bool)
forall (f :: * -> *).
BooleanR f =>
(f Bool, f Bool) -> (f Bool, f Bool)
notR ( f Bool
notZR, f Bool
forall a. Monoid a => a
mempty )
in ( f x
x', f x
y', f Bool
z' )
instance EqR Defined where
type EqC Defined = Eq
eqR :: (Defined x, Defined x, Defined Bool)
-> (Defined x, Defined x, Defined Bool)
eqR ( Defined x
x, Defined x
y, Defined Bool
z )
= ( if Defined Bool
z Defined Bool -> Defined Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Defined Bool
forall (f :: * -> *). BooleanR f => f Bool
trueR then Defined x
y else Defined x
forall a. Monoid a => a
mempty
, if Defined Bool
z Defined Bool -> Defined Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Defined Bool
forall (f :: * -> *). BooleanR f => f Bool
trueR then Defined x
x else Defined x
forall a. Monoid a => a
mempty
, (x -> x -> Bool) -> Defined x -> Defined x -> Defined Bool
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 x -> x -> Bool
forall a. Eq a => a -> a -> Bool
(==) Defined x
x Defined x
y
)
instance EqR Intersect where
type EqC Intersect = Intersectable
eqR :: (Intersect x, Intersect x, Intersect Bool)
-> (Intersect x, Intersect x, Intersect Bool)
eqR ( Intersect x
x, Intersect x
y, Intersect Bool
z )
= ( if | Intersect Bool
z Intersect Bool -> Intersect Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Intersect Bool
forall (f :: * -> *). BooleanR f => f Bool
trueR -> Intersect x
y
| Intersect Bool
z Intersect Bool -> Intersect Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Intersect Bool
forall (f :: * -> *). BooleanR f => f Bool
falseR Bool -> Bool -> Bool
&& Intersect x -> Int
forall x. Intersectable x => Intersect x -> Int
Intersect.size Intersect x
y Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 -> Intersect x -> Intersect x
forall x. Intersectable x => Intersect x -> Intersect x
Intersect.except Intersect x
y
| Bool
otherwise -> Intersect x
forall a. Monoid a => a
mempty
, if | Intersect Bool
z Intersect Bool -> Intersect Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Intersect Bool
forall (f :: * -> *). BooleanR f => f Bool
trueR -> Intersect x
x
| Intersect Bool
z Intersect Bool -> Intersect Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Intersect Bool
forall (f :: * -> *). BooleanR f => f Bool
falseR Bool -> Bool -> Bool
&& Intersect x -> Int
forall x. Intersectable x => Intersect x -> Int
Intersect.size Intersect x
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 -> Intersect x -> Intersect x
forall x. Intersectable x => Intersect x -> Intersect x
Intersect.except Intersect x
x
| Bool
otherwise -> Intersect x
forall a. Monoid a => a
mempty
, (x -> x -> Bool) -> Intersect x -> Intersect x -> Intersect Bool
forall this that result.
(Intersectable this, Intersectable that, Intersectable result) =>
(this -> that -> result)
-> Intersect this -> Intersect that -> Intersect result
Intersect.lift2 x -> x -> Bool
forall a. Eq a => a -> a -> Bool
(==) Intersect x
x Intersect x
y
)