ghc-internal-9.1001.0: Basic libraries
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilitynot portable
Safe HaskellTrustworthy
LanguageHaskell2010

GHC.Internal.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) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

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

Defined in GHC.Internal.Data.Type.Ord

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

Defined in GHC.Internal.Data.Type.Ord

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

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 

Instances

Instances details
Show (OrderingI a b) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

Eq (OrderingI a b) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

Methods

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

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

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

type family OrdCond (o :: Ordering) (lt :: k) (eq :: k) (gt :: k) :: k 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 :: k) (eq :: k) (gt :: k) = lt 
OrdCond 'EQ (lt :: k) (eq :: k) (gt :: k) = eq 
OrdCond 'GT (lt :: k) (eq :: k) (gt :: k) = gt