Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- data (a :: k) :~: (b :: k) where
- class a ~# b => (a :: k0) ~~ (b :: k1)
- 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 ...
The equality types
data (a :: k) :~: (b :: k) where infix 4 #
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
Instances
TestCoercion ((:~:) a :: k -> Type) | Since: base-4.7.0.0 |
Defined in Data.Type.Coercion | |
TestEquality ((:~:) a :: k -> Type) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0 |
a ~ b => Enum (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
Eq (a :~: b) | Since: base-4.7.0.0 |
Ord (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
a ~ b => Read (a :~: b) | Since: base-4.7.0.0 |
Show (a :~: b) | Since: base-4.7.0.0 |
class a ~# b => (a :: k0) ~~ (b :: k1) #
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.
data (a :: k1) :~~: (b :: k2) where infix 4 #
Kind heterogeneous propositional equality. Like :~:
, 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
Instances
TestCoercion ((:~~:) a :: k -> Type) | Since: base-4.10.0.0 |
Defined in Data.Type.Coercion | |
TestEquality ((:~~:) a :: k -> Type) | Since: base-4.10.0.0 |
Defined in Data.Type.Equality | |
a ~~ b => Bounded (a :~~: b) | Since: base-4.10.0.0 |
a ~~ b => Enum (a :~~: b) | Since: base-4.10.0.0 |
Defined in Data.Type.Equality succ :: (a :~~: b) -> a :~~: b # pred :: (a :~~: b) -> a :~~: b # fromEnum :: (a :~~: b) -> Int # enumFrom :: (a :~~: b) -> [a :~~: b] # enumFromThen :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] # enumFromTo :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] # enumFromThenTo :: (a :~~: b) -> (a :~~: b) -> (a :~~: b) -> [a :~~: b] # | |
Eq (a :~~: b) | Since: base-4.10.0.0 |
Ord (a :~~: b) | Since: base-4.10.0.0 |
a ~~ b => Read (a :~~: b) | Since: base-4.10.0.0 |
Show (a :~~: b) | Since: base-4.10.0.0 |
Working with equality
trans :: forall k (a :: k) (b :: k) (c :: k). (a :~: b) -> (b :~: c) -> a :~: c #
Transitivity of equality
gcastWith :: forall k (a :: k) (b :: k) r. (a :~: b) -> (a ~ b => r) -> r #
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 #
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 #
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 #
Extract equality of type constructors from an equality of applied types
Inferring equality from other types
class TestEquality (f :: k -> Type) where #
This class contains types where you can learn the equality of two types from information contained in terms. Typically, only singleton types should inhabit this class.
testEquality :: forall (a :: k) (b :: k). f a -> f b -> Maybe (a :~: b) #
Conditionally prove the equality of a
and b
.
Instances
TestEquality (TypeRep :: k -> Type) | |
Defined in Data.Typeable.Internal | |
TestEquality ((:~:) a :: k -> Type) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
TestEquality ((:~~:) a :: k -> Type) | Since: base-4.10.0.0 |
Defined in Data.Type.Equality | |
TestEquality f => TestEquality (Compose f g :: k2 -> Type) | The deduction (via generativity) that if Since: base-4.14.0.0 |
Defined in Data.Functor.Compose |