Data.Type.Equality (original) (raw)
Contents
- The equality types
- Working with equality
- Inferring equality from other types
- Boolean type-level equality
Description
Definition of propositional equality (`[:~:](Data-Type-Equality.html#t::-126-: "Data.Type.Equality")`)
. Pattern-matching on a variable of type (a `[:~:](Data-Type-Equality.html#t::-126-: "Data.Type.Equality")` b)
produces a proof that a `~` b
.
Since: base-4.7.0.0
Synopsis
- class a ~# b => (a :: k) ~ (b :: k)
- class a ~# b => (a :: k0) ~~ (b :: k1)
- data (a :: k) :~: (b :: k) where
- data (a :: k1) :~~: (b :: k2) where
- sym :: forall {k} (a :: k) (b :: k). (a :~: b) -> b :~: a
- trans :: forall {k} (a :: k) (b :: k) (c :: k). (a :~: b) -> (b :~: c) -> a :~: c
- castWith :: (a :~: b) -> a -> b
- gcastWith :: forall {k} (a :: k) (b :: k) r. (a :~: b) -> (a ~ b => r) -> r
- apply :: forall {k1} {k2} (f :: k1 -> k2) (g :: k1 -> k2) (a :: k1) (b :: k1). (f :~: g) -> (a :~: b) -> f a :~: g b
- inner :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> a :~: b
- outer :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> f :~: g
- class TestEquality (f :: k -> Type) where
- testEquality :: forall (a :: k) (b :: k). f a -> f b -> Maybe (a :~: b)
- type family (a :: k) == (b :: k) :: Bool where ...
class a ~# b => (a :: k) ~ (b :: k) infix 4 Source #
Lifted, homogeneous equality. By lifted, we mean that it can be bogus (deferred type error). By homogeneous, the two types a
and b
must have the same kinds.
class a ~# b => (a :: k0) ~~ (b :: k1) infix 4 Source #
Lifted, heterogeneous equality. By lifted, we mean that it can be bogus (deferred type error). By heterogeneous, the two types a
and b
might have different kinds. Because ~~
can appear unexpectedly in error messages to users who do not care about the difference between heterogeneous equality ~~
and homogeneous equality ~
, this is printed as ~
unless-fprint-equality-relations
is set.
In 0.7.0
, the fixity was set to infix 4
to match the fixity of [:~~:](Data-Type-Equality.html#v::-126--126-: "Data.Type.Equality")
.
data (a :: k) :~: (b :: k) where infix 4 Source #
Propositional equality. If a :~: b
is inhabited by some terminating value, then the type a
is the same as the type b
. To use this equality in practice, pattern-match on the a :~: b
to get out the Refl
constructor; in the body of the pattern-match, the compiler knows that a ~ b
.
Since: base-4.7.0.0
Constructors
| Refl :: forall {k} (a :: k). a :~: a | | | ----------------------------------------------------------------------------------------------- | |
data (a :: k1) :~~: (b :: k2) where infix 4 Source #
Kind heterogeneous propositional equality. Like [:~:](Data-Type-Equality.html#t::-126-: "Data.Type.Equality")
, a :~~: b
is inhabited by a terminating value if and only if a
is the same type as b
.
Since: base-4.10.0.0
sym :: forall {k} (a :: k) (b :: k). (a :~: b) -> b :~: a Source #
Symmetry of equality
trans :: forall {k} (a :: k) (b :: k) (c :: k). (a :~: b) -> (b :~: c) -> a :~: c Source #
Transitivity of equality
gcastWith :: forall {k} (a :: k) (b :: k) r. (a :~: b) -> (a ~ b => r) -> r Source #
Generalized form of type-safe cast using propositional equality
apply :: forall {k1} {k2} (f :: k1 -> k2) (g :: k1 -> k2) (a :: k1) (b :: k1). (f :~: g) -> (a :~: b) -> f a :~: g b Source #
Apply one equality to another, respectively
inner :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> a :~: b Source #
Extract equality of the arguments from an equality of applied types
outer :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> f :~: g Source #
Extract equality of type constructors from an equality of applied types
Inferring equality from other types
class TestEquality (f :: k -> Type) where Source #
This class contains types where you can learn the equality of two types from information contained in terms.
The result should be Just Refl
if and only if the types applied to f
are equal:
testEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b
Typically, only singleton types should inhabit this class. In that case type argument equality coincides with term equality:
testEquality (x :: f a) (y :: f b) = Just Refl ⟺ a = b ⟺ x = y
isJust (testEquality x y) = x == y
Singleton types are not required, however, and so the latter two would-be laws are not in fact valid in general.
type family (a :: k) == (b :: k) :: Bool where ... infix 4 Source #
A type family to compute Boolean equality.
Equations
| (f a :: k2) == (g b :: k2) = (f == g) && (a == b) | | | ---------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- | | | (a :: k) == (a :: k) = 'True | | | (_1 :: k) == (_2 :: k) = 'False | |