heterogeneous-comparison
Copyright(c) L. S. Leary 2025
Safe HaskellNone
LanguageGHC2021

Data.Hetero.Eq

Description

Heterogeneous equality with evidence capture.

Synopsis

HetEq

class HetEq (f :: k -> Type) where Source #

Heterogeneous equality with evidence capture of type equivalence.

Associated Types

type Strength (f :: k -> Type) :: RoleKind Source #

Does not correspond precisely to the role signature of f according to GHC, but rather a lower bound on the Strength of the evidence gleaned from a positive equality test.

Methods

heq :: forall (a :: k) (b :: k). f a -> f b -> Maybe (AtLeast (Strength f) a b) Source #

Compare an f a and an f b for equality, opportunistically capturing the strongest type-equivalence evidence we can given the arguments.

Instances

Instances details
HetEq SNat Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength SNat 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: forall (a :: Nat) (b :: Nat). SNat a -> SNat b -> Maybe (AtLeast (Strength SNat) a b) Source #

HetEq Role Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength Role 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: forall (a :: RoleKind) (b :: RoleKind). Role a -> Role b -> Maybe (AtLeast (Strength Role) a b) Source #

HetEq SChar Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength SChar 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (AtLeast (Strength SChar) a b) Source #

HetEq SSymbol Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength SSymbol 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: forall (a :: Symbol) (b :: Symbol). SSymbol a -> SSymbol b -> Maybe (AtLeast (Strength SSymbol) a b) Source #

HetEq Chan Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength Chan 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: Chan a -> Chan b -> Maybe (AtLeast (Strength Chan) a b) Source #

HetEq TVar Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength TVar 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: TVar a -> TVar b -> Maybe (AtLeast (Strength TVar) a b) Source #

HetEq IORef Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength IORef 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: IORef a -> IORef b -> Maybe (AtLeast (Strength IORef) a b) Source #

HetEq MVar Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength MVar 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: MVar a -> MVar b -> Maybe (AtLeast (Strength MVar) a b) Source #

HetEq Array Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength Array 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: Array a -> Array b -> Maybe (AtLeast (Strength Array) a b) Source #

HetEq SmallArray Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength SmallArray 
Instance details

Defined in Data.Hetero.Eq

HetEq TBQueue Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength TBQueue 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: TBQueue a -> TBQueue b -> Maybe (AtLeast (Strength TBQueue) a b) Source #

HetEq TChan Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength TChan 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: TChan a -> TChan b -> Maybe (AtLeast (Strength TChan) a b) Source #

HetEq TMVar Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength TMVar 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: TMVar a -> TMVar b -> Maybe (AtLeast (Strength TMVar) a b) Source #

HetEq TQueue Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength TQueue 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: TQueue a -> TQueue b -> Maybe (AtLeast (Strength TQueue) a b) Source #

HetEq (STRef s :: Type -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (STRef s :: Type -> Type) 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: STRef s a -> STRef s b -> Maybe (AtLeast (Strength (STRef s)) a b) Source #

HetEq (MutableArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (MutableArray s :: Type -> Type) 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: MutableArray s a -> MutableArray s b -> Maybe (AtLeast (Strength (MutableArray s)) a b) Source #

HetEq (MVar s :: Type -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (MVar s :: Type -> Type) 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: MVar s a -> MVar s b -> Maybe (AtLeast (Strength (MVar s)) a b) Source #

HetEq (MutVar s :: Type -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (MutVar s :: Type -> Type) 
Instance details

Defined in Data.Hetero.Eq

Methods

heq :: MutVar s a -> MutVar s b -> Maybe (AtLeast (Strength (MutVar s)) a b) Source #

HetEq (SmallMutableArray s :: Type -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (SmallMutableArray s :: Type -> Type) 
Instance details

Defined in Data.Hetero.Eq

HetEq (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (Proxy :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (Proxy :: k -> Type) = 'Phantom

Methods

heq :: forall (a :: k) (b :: k). Proxy a -> Proxy b -> Maybe (AtLeast (Strength (Proxy :: k -> Type)) a b) Source #

HetEq (TypeRep :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (TypeRep :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (TypeRep :: k -> Type) = Strength (TestEq (TypeRep :: k -> Type))

Methods

heq :: forall (a :: k) (b :: k). TypeRep a -> TypeRep b -> Maybe (AtLeast (Strength (TypeRep :: k -> Type)) a b) Source #

HetEq (ID :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.ID

Associated Types

type Strength (ID :: k -> Type) 
Instance details

Defined in Data.Hetero.ID

type Strength (ID :: k -> Type) = 'Representational

Methods

heq :: forall (a :: k) (b :: k). ID a -> ID b -> Maybe (AtLeast (Strength (ID :: k -> Type)) a b) Source #

HetEq (VoidF :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Void

Associated Types

type Strength (VoidF :: k -> Type) 
Instance details

Defined in Data.Hetero.Void

type Strength (VoidF :: k -> Type) = 'Nominal

Methods

heq :: forall (a :: k) (b :: k). VoidF a -> VoidF b -> Maybe (AtLeast (Strength (VoidF :: k -> Type)) a b) Source #

Eq a => HetEq (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (Const a :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (Const a :: k -> Type) = 'Phantom

Methods

heq :: forall (a0 :: k) (b :: k). Const a a0 -> Const a b -> Maybe (AtLeast (Strength (Const a :: k -> Type)) a0 b) Source #

HetEq (Coercion a :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (Coercion a :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (Coercion a :: k -> Type) = Strength (TestCo (Coercion a))

Methods

heq :: forall (a0 :: k) (b :: k). Coercion a a0 -> Coercion a b -> Maybe (AtLeast (Strength (Coercion a)) a0 b) Source #

HetEq ((:~:) a :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength ((:~:) a :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength ((:~:) a :: k -> Type) = Strength (TestEq ((:~:) a))

Methods

heq :: forall (a0 :: k) (b :: k). (a :~: a0) -> (a :~: b) -> Maybe (AtLeast (Strength ((:~:) a)) a0 b) Source #

TestCoercion f => HetEq (TestCo f :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (TestCo f :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (TestCo f :: k -> Type) = 'Representational

Methods

heq :: forall (a :: k) (b :: k). TestCo f a -> TestCo f b -> Maybe (AtLeast (Strength (TestCo f)) a b) Source #

TestEquality f => HetEq (TestEq f :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (TestEq f :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (TestEq f :: k -> Type) = 'Nominal

Methods

heq :: forall (a :: k) (b :: k). TestEq f a -> TestEq f b -> Maybe (AtLeast (Strength (TestEq f)) a b) Source #

(HetEq' f, HetEq' g) => HetEq (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (Product f g :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (Product f g :: k -> Type) = Max (Strength f) (Strength g)

Methods

heq :: forall (a :: k) (b :: k). Product f g a -> Product f g b -> Maybe (AtLeast (Strength (Product f g)) a b) Source #

(HetEq' f, HetEq' g) => HetEq (Sum f g :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (Sum f g :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (Sum f g :: k -> Type) = Min (Strength f) (Strength g)

Methods

heq :: forall (a :: k) (b :: k). Sum f g a -> Sum f g b -> Maybe (AtLeast (Strength (Sum f g)) a b) Source #

HetEq ((:~~:) a :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength ((:~~:) a :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength ((:~~:) a :: k -> Type) = Strength (TestEq ((:~~:) a :: k -> Type))

Methods

heq :: forall (a0 :: k) (b :: k). (a :~~: a0) -> (a :~~: b) -> Maybe (AtLeast (Strength ((:~~:) a :: k -> Type)) a0 b) Source #

HetEq (AtLeast r a :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (AtLeast r a :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (AtLeast r a :: k -> Type) = r

Methods

heq :: forall (a0 :: k) (b :: k). AtLeast r a a0 -> AtLeast r a b -> Maybe (AtLeast (Strength (AtLeast r a)) a0 b) Source #

HetEq (Exactly r a :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (Exactly r a :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (Exactly r a :: k -> Type) = r

Methods

heq :: forall (a0 :: k) (b :: k). Exactly r a a0 -> Exactly r a b -> Maybe (AtLeast (Strength (Exactly r a)) a0 b) Source #

(HetEq f, SuperPhantom g) => HetEq (Compose f g :: k2 -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (Compose f g :: k1 -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (Compose f g :: k1 -> Type) = Strength f

Methods

heq :: forall (a :: k2) (b :: k2). Compose f g a -> Compose f g b -> Maybe (AtLeast (Strength (Compose f g)) a b) Source #

type HetEq' (f :: k -> Type) = (KnownRole (Strength f), HetEq f) Source #

Newtypes for DerivingVia

newtype TestCo (f :: k -> Type) (a :: k) Source #

Derives a HetEq instance from TestCoercion.

Constructors

TestCo (f a) 

Instances

Instances details
TestCoercion f => HetEq (TestCo f :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (TestCo f :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (TestCo f :: k -> Type) = 'Representational

Methods

heq :: forall (a :: k) (b :: k). TestCo f a -> TestCo f b -> Maybe (AtLeast (Strength (TestCo f)) a b) Source #

type Strength (TestCo f :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

type Strength (TestCo f :: k -> Type) = 'Representational

newtype TestEq (f :: k -> Type) (a :: k) Source #

Derives a HetEq instance from TestEquality.

Constructors

TestEq (f a) 

Instances

Instances details
TestEquality f => HetEq (TestEq f :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

Associated Types

type Strength (TestEq f :: k -> Type) 
Instance details

Defined in Data.Hetero.Eq

type Strength (TestEq f :: k -> Type) = 'Nominal

Methods

heq :: forall (a :: k) (b :: k). TestEq f a -> TestEq f b -> Maybe (AtLeast (Strength (TestEq f)) a b) Source #

type Strength (TestEq f :: k -> Type) Source # 
Instance details

Defined in Data.Hetero.Eq

type Strength (TestEq f :: k -> Type) = 'Nominal