{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Control.FX.EqIn (
EqIn(..)
, Context(..)
) where
import Data.Typeable (Typeable, typeOf)
class EqIn (t :: * -> *)
where
data Context t
eqIn
:: (Eq a)
=> Context t
-> t a
-> t a
-> Bool
instance
EqIn Maybe
where
data Context Maybe
= MaybeCtx
{ unMaybeCtx :: ()
} deriving (Eq, Show)
eqIn
:: (Eq a)
=> Context Maybe
-> Maybe a
-> Maybe a
-> Bool
eqIn _ = (==)
instance
( Eq a
) => EqIn (Either a)
where
data Context (Either a)
= EitherCtx
{ unEitherCtx :: ()
} deriving (Eq, Show)
eqIn
:: (Eq b)
=> Context (Either a)
-> Either a b
-> Either a b
-> Bool
eqIn _ = (==)