eq-4.2.1: Leibnizian equality

Copyright(C) 2011-2014 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityrank2 types, type operators, (optional) type families
Safe HaskellNone
LanguageHaskell2010

Data.Eq.Type

Contents

Description

Leibnizian equality. Injectivity in the presence of type families is provided by a generalization of a trick by Oleg Kiselyov posted here:

http://www.haskell.org/pipermail/haskell-cafe/2010-May/077177.html

Synopsis

Leibnizian equality

newtype a := b infixl 4 Source #

Leibnizian equality states that two things are equal if you can substitute one for the other in all contexts

Constructors

Refl 

Fields

  • subst :: forall c. c a -> c b
     
Instances
Category ((:=) :: k -> k -> Type) Source #

Equality forms a category

Instance details

Defined in Data.Eq.Type

Methods

id :: a := a #

(.) :: (b := c) -> (a := b) -> a := c #

Groupoid ((:=) :: k -> k -> Type) Source # 
Instance details

Defined in Data.Eq.Type

Methods

inv :: (a := b) -> b := a #

Semigroupoid ((:=) :: k -> k -> Type) Source # 
Instance details

Defined in Data.Eq.Type

Methods

o :: (j := k1) -> (i := j) -> i := k1 #

TestCoercion ((:=) a :: k -> Type) Source # 
Instance details

Defined in Data.Eq.Type

Methods

testCoercion :: (a := a0) -> (a := b) -> Maybe (Coercion a0 b) #

TestEquality ((:=) a :: k -> Type) Source # 
Instance details

Defined in Data.Eq.Type

Methods

testEquality :: (a := a0) -> (a := b) -> Maybe (a0 :~: b) #

Equality as an equivalence relation

refl :: a := a Source #

Equality is reflexive

trans :: (a := b) -> (b := c) -> a := c Source #

Equality is transitive

symm :: (a := b) -> b := a Source #

Equality is symmetric

coerce :: (a := b) -> a -> b Source #

If two things are equal you can convert one to the other

Lifting equality

lift :: (a := b) -> f a := f b Source #

You can lift equality into any type constructor

lift2 :: (a := b) -> f a c := f b c Source #

... in any position

lift2' :: (a := b) -> (c := d) -> f a c := f b d Source #

lift3 :: (a := b) -> f a c d := f b c d Source #

lift3' :: (a := b) -> (c := d) -> (e := f) -> g a c e := g b d f Source #

Lowering equality

lower :: forall a b f. (f a := f b) -> a := b Source #

Type constructors are injective, so you can lower equality through any type constructor ...

lower2 :: forall a b c f. (f a c := f b c) -> a := b Source #

... in any position ...

lower3 :: forall a b c d f. (f a c d := f b c d) -> a := b Source #

... these definitions are poly-kinded on GHC 7.6 and up.

:~: equivalence

Data.Type.Equality GADT definition is equivalent in power

fromLeibniz :: (a := b) -> a :~: b Source #

toLeibniz :: (a :~: b) -> a := b Source #

Coercion conversion

Leibnizian equality can be converted to representational equality

reprLeibniz :: (a := b) -> Coercion a b Source #