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

Data.Hetero.PtrEq

Description

Heterogeneous pointer equality.

The offerings of this module should eventually be incorporated into base, stm and primitive by:

  • Generalising the types of pointer equality primitives (#24994)
  • Thereby providing TestCoercion instances for the the boxings of those primitive types (#17076)
  • Thereby providing TestCoercion instances for derived types
Synopsis

Pointer Equality

Primitive

GHC.Exts provides pointer equality functions for primitive unlifted types of the form:

sameFoo# :: Foo# a -> Foo# a -> Int#

When appropriate, we generalise the above to:

sameFoo# :: Foo# a -> Foo# b -> Maybe (Coercion a b)

\[ \]

data Array# (a :: TYPE ('BoxedRep l)) :: UnliftedType #

sameArray# Source #

Arguments

:: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). Array# a 
-> Array# b 
-> Maybe (Coercion a b) 

data MutableArray# a (b :: TYPE ('BoxedRep l)) :: UnliftedType #

sameMutableArray# Source #

Arguments

:: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). MutableArray# s a 
-> MutableArray# s b 
-> Maybe (Coercion a b) 

data SmallArray# (a :: TYPE ('BoxedRep l)) :: UnliftedType #

sameSmallArray# Source #

Arguments

:: forall {l :: Levity} (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). SmallArray# a 
-> SmallArray# b 
-> Maybe (Coercion a b) 

sameSmallMutableArray# Source #

Arguments

:: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). SmallMutableArray# s a 
-> SmallMutableArray# s b 
-> Maybe (Coercion a b) 

data MutVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType #

A MutVar# behaves like a single-element mutable array.

sameMutVar# Source #

Arguments

:: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). MutVar# s a 
-> MutVar# s b 
-> Maybe (Coercion a b) 

data TVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType #

sameTVar# Source #

Arguments

:: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). TVar# s a 
-> TVar# s b 
-> Maybe (Coercion a b) 

data MVar# a (b :: TYPE ('BoxedRep l)) :: UnliftedType #

A shared mutable variable (not the same as a MutVar#!). (Note: in a non-concurrent implementation, (MVar# a) can be represented by (MutVar# (Maybe a)).)

sameMVar# Source #

Arguments

:: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). MVar# s a 
-> MVar# s b 
-> Maybe (Coercion a b) 

data IOPort# a (b :: TYPE ('BoxedRep l)) :: UnliftedType #

A shared I/O port is almost the same as an MVar#. The main difference is that IOPort has no deadlock detection or deadlock breaking code that forcibly releases the lock.

sameIOPort# Source #

Arguments

:: forall {l :: Levity} s (a :: TYPE ('BoxedRep l)) (b :: TYPE ('BoxedRep l)). IOPort# s a 
-> IOPort# s b 
-> Maybe (Coercion a b) 

Derived

There are various types in base and stm derived from the primitive types above, but for which opacity precludes leveraging the corresponding functions. Accordingly, we provide additional sameFoo functions for them here.

\[ \]

data Chan a #

Chan is an abstract type representing an unbounded FIFO channel.

Instances

Instances details
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 #

Eq (Chan a)

Since: base-4.4.0.0

Instance details

Defined in Control.Concurrent.Chan

Methods

(==) :: Chan a -> Chan a -> Bool #

(/=) :: Chan a -> Chan a -> Bool #

type Strength Chan Source # 
Instance details

Defined in Data.Hetero.Eq

sameChan :: Chan a -> Chan b -> Maybe (Coercion a b) Source #

data TBQueue a #

TBQueue is an abstract type representing a bounded FIFO channel.

Since: stm-2.4

Instances

Instances details
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 #

Eq (TBQueue a) 
Instance details

Defined in Control.Concurrent.STM.TBQueue

Methods

(==) :: TBQueue a -> TBQueue a -> Bool #

(/=) :: TBQueue a -> TBQueue a -> Bool #

type Strength TBQueue Source # 
Instance details

Defined in Data.Hetero.Eq

data TChan a #

TChan is an abstract type representing an unbounded FIFO channel.

Instances

Instances details
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 #

Eq (TChan a) 
Instance details

Defined in Control.Concurrent.STM.TChan

Methods

(==) :: TChan a -> TChan a -> Bool #

(/=) :: TChan a -> TChan a -> Bool #

type Strength TChan Source # 
Instance details

Defined in Data.Hetero.Eq

data TMVar a #

A TMVar is a synchronising variable, used for communication between concurrent threads. It can be thought of as a box, which may be empty or full.

Instances

Instances details
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 #

Eq (TMVar a) 
Instance details

Defined in Control.Concurrent.STM.TMVar

Methods

(==) :: TMVar a -> TMVar a -> Bool #

(/=) :: TMVar a -> TMVar a -> Bool #

type Strength TMVar Source # 
Instance details

Defined in Data.Hetero.Eq

data TQueue a #

TQueue is an abstract type representing an unbounded FIFO channel.

Since: stm-2.4

Instances

Instances details
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 #

Eq (TQueue a) 
Instance details

Defined in Control.Concurrent.STM.TQueue

Methods

(==) :: TQueue a -> TQueue a -> Bool #

(/=) :: TQueue a -> TQueue a -> Bool #

type Strength TQueue Source # 
Instance details

Defined in Data.Hetero.Eq