base-4.16.1.0: Basic libraries
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilitynot portable
Safe HaskellSafe
LanguageHaskell2010

Data.Type.Ord

Description

Basic operations on type-level Orderings.

Since: base-4.16.0.0

Synopsis

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

Instances

Instances details
type Compare (a :: Natural) (b :: Natural) # 
Instance details

Defined in Data.Type.Ord

type Compare (a :: Natural) (b :: Natural) = CmpNat a b
type Compare (a :: Char) (b :: Char) # 
Instance details

Defined in Data.Type.Ord

type Compare (a :: Char) (b :: Char) = CmpChar a b
type Compare (a :: Symbol) (b :: Symbol) # 
Instance details

Defined in Data.Type.Ord

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b

data OrderingI a b where Source #

Ordering data type for type literals that provides proof of their ordering.

Since: base-4.16.0.0

Constructors

LTI :: Compare a b ~ 'LT => OrderingI a b 
EQI :: Compare a a ~ 'EQ => OrderingI a a 
GTI :: Compare a b ~ 'GT => OrderingI a b 

Instances

Instances details
Show (OrderingI a b) # 
Instance details

Defined in Data.Type.Ord

Eq (OrderingI a b) # 
Instance details

Defined in Data.Type.Ord

Methods

(==) :: OrderingI a b -> OrderingI a b -> Bool Source #

(/=) :: OrderingI a b -> OrderingI a b -> Bool Source #

type (<=) x y = (x <=? y) ~ 'True infix 4 Source #

Comparison (<=) of comparable types, as a constraint.

Since: base-4.16.0.0

type (<=?) m n = 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 y = (x >=? y) ~ 'True infix 4 Source #

Comparison (>=) of comparable types, as a constraint.

Since: base-4.16.0.0

type (>=?) m n = 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 y = (x >? y) ~ 'True infix 4 Source #

Comparison (>) of comparable types, as a constraint.

Since: base-4.16.0.0

type (>?) m n = 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 y = (x <? y) ~ 'True infix 4 Source #

Comparison (<) of comparable types, as a constraint.

Since: base-4.16.0.0

type (<?) m n = 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 n = OrdCond (Compare m n) n n m Source #

Maximum between two comparable types.

Since: base-4.16.0.0

type Min m n = OrdCond (Compare m n) m m n Source #

Minimum between two comparable types.

Since: base-4.16.0.0

type family OrdCond o lt eq gt where ... Source #

A case statement on Ordering.

OrdCond c l e g is l when c ~ LT, e when c ~ EQ, and g when c ~ GT.

Since: base-4.16.0.0

Equations

OrdCond 'LT lt eq gt = lt 
OrdCond 'EQ lt eq gt = eq 
OrdCond 'GT lt eq gt = gt