| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Kinds.Ord
Description
Type-level Ord.
On recent versions of base, this just re-exports things from
Data.Type.Ord. On older versions, it provides its own implementation,
moved from older versions of numeric-kinds.
Synopsis
- type family Compare (x :: k) (y :: k) :: Ordering
- type (<?) x y = CompareCond x y True False False
- type (<=?) x y = CompareCond x y True True False
- type (==?) x y = CompareCond x y False True False
- type (/=?) x y = CompareCond x y True False True
- type (>=?) x y = CompareCond x y False True True
- type (>?) x y = CompareCond x y False False True
- type (<) x y = Proven (x <? y)
- type (<=) x y = Proven (x <=? y)
- type (==) x y = Proven (x ==? y)
- type (/=) x y = Proven (x /=? y)
- type (>=) x y = Proven (x >=? y)
- type (>) x y = Proven (x >? y)
- type Max x y = CompareCond x y y y x
- type Min x y = CompareCond x y x x y
- data OrderingI m n where
- type Proven b = b ~ 'True
- type family OrdCond (o :: Ordering) (lt :: k) (eq :: k) (gt :: k) :: k where ...
- type CompareCond x y lt eq gt = OrdCond (Compare x y) lt eq gt
Comparisons
type family Compare (x :: k) (y :: k) :: Ordering Source #
Type-level Ord "kindclass".
Note this has an invisible dependent k parameter that makes the
textually-identical instances for different kinds actually different. Neat!
Inequality Constraints
Selection
type Max x y = CompareCond x y y y x Source #
type Min x y = CompareCond x y x x y Source #
Proof Witnesses
data OrderingI m n where Source #
Ordering results carrying evidence of type-level ordering relations.
Utility
type family OrdCond (o :: Ordering) (lt :: k) (eq :: k) (gt :: k) :: k where ... Source #
Type-level eliminator for Ordering.
OrdCond o lt eq gt selects from among lt, eq, and gt according
to o.
type CompareCond x y lt eq gt = OrdCond (Compare x y) lt eq gt Source #
CompareCond x y lt eq gt is lt if x is less than y, and so on.