Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- module Data.Type.Coercion.Related
- data IsUnion x y z = IsUnion {}
- withUnion :: Related x y -> (forall xy. IsUnion x y xy -> r) -> r
- unique :: IsUnion x y z -> IsUnion x y z' -> Coercion z z'
- greater :: Sub x y -> IsUnion x y y
- idemp :: IsUnion x x x
- commutative :: IsUnion x y z -> IsUnion y x z
- associative :: IsUnion x y xy -> IsUnion xy z xyz -> IsUnion y z yz -> IsUnion x yz xyz
Documentation
module Data.Type.Coercion.Related
IsUnion x y z
witnesses the fact:
- All
x, y, z
share the same runtime representation z
is a union type ofx
andy
. In other words, the following three holds:Sub
x zSub y z
- For any type
r
satisfying both of(Sub x r, Sub y r)
,Sub z r
.
Instances
TestCoercion (IsUnion x y :: Type -> Type) Source # | |
Defined in Newtype.Union | |
Eq (IsUnion x y z) Source # | |
Ord (IsUnion x y z) Source # | |
Defined in Newtype.Union compare :: IsUnion x y z -> IsUnion x y z -> Ordering # (<) :: IsUnion x y z -> IsUnion x y z -> Bool # (<=) :: IsUnion x y z -> IsUnion x y z -> Bool # (>) :: IsUnion x y z -> IsUnion x y z -> Bool # (>=) :: IsUnion x y z -> IsUnion x y z -> Bool # |
withUnion :: Related x y -> (forall xy. IsUnion x y xy -> r) -> r Source #
For a pair of Related
types x
and y
, make some (existentially quantified)
type xy
where xy
is a union type of x, y
.
unique :: IsUnion x y z -> IsUnion x y z' -> Coercion z z' Source #
Two union types z,z'
of the same pair of types x,y
may be different,
but they are equivalent in terms of coercibility.
idemp :: IsUnion x x x Source #
Union is idempotent.
Note: combining idemp
and unique
, IsUnion x x z -> Coercion x z
holds.