| License | BSD-style (see the LICENSE file in the distribution) | 
|---|---|
| Maintainer | libraries@haskell.org | 
| Stability | stable | 
| Portability | not portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Type.Ord
Description
Basic operations on type-level Orderings.
Since: base-4.16.0.0
Synopsis
- type family Compare (a :: k) (b :: k) :: Ordering
- data OrderingI (a :: k) (b :: k) where
- type (<=) (x :: t) (y :: t) = Assert (x <=? y) (LeErrMsg x y :: Constraint)
- type (<=?) (m :: k) (n :: k) = OrdCond (Compare m n) 'True 'True 'False
- type (>=) (x :: t) (y :: t) = Assert (x >=? y) (GeErrMsg x y :: Constraint)
- type (>=?) (m :: k) (n :: k) = OrdCond (Compare m n) 'False 'True 'True
- type (>) (x :: t) (y :: t) = Assert (x >? y) (GtErrMsg x y :: Constraint)
- type (>?) (m :: k) (n :: k) = OrdCond (Compare m n) 'False 'False 'True
- type (<) (x :: t) (y :: t) = Assert (x <? y) (LtErrMsg x y :: Constraint)
- type (<?) (m :: k) (n :: k) = OrdCond (Compare m n) 'True 'False 'False
- type Max (m :: k) (n :: k) = OrdCond (Compare m n) n n m
- type Min (m :: k) (n :: k) = OrdCond (Compare m n) m m n
- type family OrdCond (o :: Ordering) (lt :: k) (eq :: k) (gt :: k) :: k where ...
Documentation
type family Compare (a :: k) (b :: k) :: Ordering Source #
Compare branches on the kind of its arguments to either compare by
 Symbol or Nat.
Since: base-4.16.0.0
data OrderingI (a :: k) (b :: k) where Source #
Ordering data type for type literals that provides proof of their ordering.
Since: base-4.16.0.0
Constructors
| LTI :: forall {k} (a :: k) (b :: k). Compare a b ~ 'LT => OrderingI a b | |
| EQI :: forall {k} (a :: k). Compare a a ~ 'EQ => OrderingI a a | |
| GTI :: forall {k} (a :: k) (b :: k). Compare a b ~ 'GT => OrderingI a b | 
type (<=) (x :: t) (y :: t) = Assert (x <=? y) (LeErrMsg x y :: Constraint) infix 4 Source #
Comparison (<=) of comparable types, as a constraint.
Since: base-4.16.0.0
type (<=?) (m :: k) (n :: k) = OrdCond (Compare m n) 'True 'True 'False infix 4 Source #
Comparison (<=) of comparable types, as a function.
Since: base-4.16.0.0
type (>=) (x :: t) (y :: t) = Assert (x >=? y) (GeErrMsg x y :: Constraint) infix 4 Source #
Comparison (>=) of comparable types, as a constraint.
Since: base-4.16.0.0
type (>=?) (m :: k) (n :: k) = OrdCond (Compare m n) 'False 'True 'True infix 4 Source #
Comparison (>=) of comparable types, as a function.
Since: base-4.16.0.0
type (>) (x :: t) (y :: t) = Assert (x >? y) (GtErrMsg x y :: Constraint) infix 4 Source #
Comparison (>) of comparable types, as a constraint.
Since: base-4.16.0.0
type (>?) (m :: k) (n :: k) = OrdCond (Compare m n) 'False 'False 'True infix 4 Source #
Comparison (>) of comparable types, as a function.
Since: base-4.16.0.0
type (<) (x :: t) (y :: t) = Assert (x <? y) (LtErrMsg x y :: Constraint) infix 4 Source #
Comparison (<) of comparable types, as a constraint.
Since: base-4.16.0.0
type (<?) (m :: k) (n :: k) = OrdCond (Compare m n) 'True 'False 'False infix 4 Source #
Comparison (<) of comparable types, as a function.
Since: base-4.16.0.0
type Max (m :: k) (n :: k) = OrdCond (Compare m n) n n m Source #
Maximum between two comparable types.
Since: base-4.16.0.0
type Min (m :: k) (n :: k) = OrdCond (Compare m n) m m n Source #
Minimum between two comparable types.
Since: base-4.16.0.0