| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Data.GADT.Compare
Synopsis
- class GEq f => GCompare f where
- data GOrdering a b where
- class GEq f where
- type (:=) = (:~:)
- defaultEq :: GEq f => f a -> f b -> Bool
- defaultNeq :: GEq f => f a -> f b -> Bool
- weakenOrdering :: GOrdering a b -> Ordering
- defaultCompare :: GCompare f => f a -> f b -> Ordering
- data (a :: k) :~: (b :: k) :: forall k. k -> k -> Type where
Documentation
class GEq f => GCompare f where Source #
Type class for comparable GADT-like structures.  When 2 things are equal,
 must return a witness that their parameter types are equal as well (GEQ).
data GOrdering a b where Source #
A type for the result of comparing GADT constructors; the type parameters of the GADT values being compared are included so that in the case where they are equal their parameter types can be unified.
Instances
| GRead (GOrdering a :: k -> Type) Source # | |
| Defined in Data.GADT.Compare | |
| GShow (GOrdering a :: k -> Type) Source # | |
| Defined in Data.GADT.Compare | |
| Eq (GOrdering a b) Source # | |
| Ord (GOrdering a b) Source # | |
| Defined in Data.GADT.Compare Methods compare :: GOrdering a b -> GOrdering a b -> Ordering # (<) :: GOrdering a b -> GOrdering a b -> Bool # (<=) :: GOrdering a b -> GOrdering a b -> Bool # (>) :: GOrdering a b -> GOrdering a b -> Bool # (>=) :: GOrdering a b -> GOrdering a b -> Bool # | |
| Show (GOrdering a b) Source # | |
A class for type-contexts which contain enough information to (at least in some cases) decide the equality of types occurring within them.
Methods
geq :: f a -> f b -> Maybe (a :~: b) Source #
Produce a witness of type-equality, if one exists.
A handy idiom for using this would be to pattern-bind in the Maybe monad, eg.:
extract :: GEq tag => tag a -> DSum tag -> Maybe a
extract t1 (t2 :=> x) = do
    Refl <- geq t1 t2
    return xOr in a list comprehension:
extractMany :: GEq tag => tag a -> [DSum tag] -> [a] extractMany t1 things = [ x | (t2 :=> x) <- things, Refl <- maybeToList (geq t1 t2)]
(Making use of the DSum type from Data.Dependent.Sum in both examples)
Deprecated: use '(:~:)' from 'Data.Type,Equality'.
Backwards compatibility alias; as of GHC 7.8, this is the same as `(:~:)`.
defaultEq :: GEq f => f a -> f b -> Bool Source #
If f has a GEq instance, this function makes a suitable default
 implementation of '(==)'.
defaultNeq :: GEq f => f a -> f b -> Bool Source #
If f has a GEq instance, this function makes a suitable default
 implementation of '(/=)'.
weakenOrdering :: GOrdering a b -> Ordering Source #
TODO: Think of a better name
This operation forgets the phantom types of a GOrdering value.
defaultCompare :: GCompare f => f a -> f b -> Ordering Source #
data (a :: k) :~: (b :: k) :: forall k. k -> k -> Type 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
| TestEquality ((:~:) a :: k -> Type) | Since: base-4.7.0.0 | 
| Defined in Data.Type.Equality | |
| GRead ((:~:) a :: k -> Type) Source # | |
| Defined in Data.GADT.Show | |
| GShow ((:~:) a :: k -> Type) Source # | |
| Defined in Data.GADT.Show | |
| GCompare ((:~:) a :: k -> Type) Source # | |
| GEq ((:~:) a :: k -> Type) Source # | |
| 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 Methods 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.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 |