singletons-2.4: A framework for generating singleton types

Copyright(C) 2014 Jan Stolarek
LicenseBSD-style (see LICENSE)
MaintainerJan Stolarek (jan.stolarek@p.lodz.pl)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Promotion.Prelude.Ord

Contents

Description

Provides promoted definitions related to type-level comparisons.

Synopsis

Documentation

class PEq a => POrd (a :: Type) Source #

Associated Types

type Compare (arg :: a) (arg :: a) :: Ordering Source #

type (arg :: a) < (arg :: a) :: Bool Source #

type (arg :: a) <= (arg :: a) :: Bool Source #

type (arg :: a) > (arg :: a) :: Bool Source #

type (arg :: a) >= (arg :: a) :: Bool Source #

type Max (arg :: a) (arg :: a) :: a Source #

type Min (arg :: a) (arg :: a) :: a Source #

Instances
POrd Bool Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd Ordering Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd () Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd Void Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd [a] Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (Maybe a) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (NonEmpty a) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (Either a b) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d, e) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d, e, f) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (a, b, c, d, e, f, g) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

type family Comparing (a :: TyFun b a -> Type) (a :: b) (a :: b) :: Ordering where ... Source #

Equations

Comparing p x y = Apply (Apply CompareSym0 (Apply p x)) (Apply p y) 

type family ThenCmp (a :: Ordering) (a :: Ordering) :: Ordering where ... Source #

Equations

ThenCmp EQ x = x 
ThenCmp LT _ = LTSym0 
ThenCmp GT _ = GTSym0 

Defunctionalization symbols

data ThenCmpSym1 (l :: Ordering) (l :: TyFun Ordering Ordering) Source #

Instances
SuppressUnusedWarnings ThenCmpSym1 Source # 
Instance details
type Apply (ThenCmpSym1 l1 :: TyFun Ordering Ordering -> *) (l2 :: Ordering) Source # 
Instance details
type Apply (ThenCmpSym1 l1 :: TyFun Ordering Ordering -> *) (l2 :: Ordering) = ThenCmp l1 l2

type ThenCmpSym2 (t :: Ordering) (t :: Ordering) = ThenCmp t t Source #

type LTSym0 = LT Source #

type EQSym0 = EQ Source #

type GTSym0 = GT Source #

data CompareSym0 (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type)) Source #

Instances
SuppressUnusedWarnings (CompareSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type) -> *) Source # 
Instance details
type Apply (CompareSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply (CompareSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Ordering -> Type) -> *) (l :: a6989586621679303258) = CompareSym1 l

data CompareSym1 (l :: a6989586621679303258) (l :: TyFun a6989586621679303258 Ordering) Source #

Instances
SuppressUnusedWarnings (CompareSym1 :: a6989586621679303258 -> TyFun a6989586621679303258 Ordering -> *) Source # 
Instance details
type Apply (CompareSym1 l1 :: TyFun a Ordering -> *) (l2 :: a) Source # 
Instance details
type Apply (CompareSym1 l1 :: TyFun a Ordering -> *) (l2 :: a) = Compare l1 l2

type CompareSym2 (t :: a6989586621679303258) (t :: a6989586621679303258) = Compare t t Source #

data (<@#@$) (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type)) Source #

Instances
SuppressUnusedWarnings ((<@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
type Apply ((<@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply ((<@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) = (<@#@$$) l

data (l :: a6989586621679303258) <@#@$$ (l :: TyFun a6989586621679303258 Bool) Source #

Instances
SuppressUnusedWarnings ((<@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
type Apply ((<@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) Source # 
Instance details
type Apply ((<@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 < l2

type (<@#@$$$) (t :: a6989586621679303258) (t :: a6989586621679303258) = (<) t t Source #

data (<=@#@$) (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type)) Source #

Instances
SuppressUnusedWarnings ((<=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
type Apply ((<=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply ((<=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) = (<=@#@$$) l

data (l :: a6989586621679303258) <=@#@$$ (l :: TyFun a6989586621679303258 Bool) Source #

Instances
SuppressUnusedWarnings ((<=@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
type Apply ((<=@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) Source # 
Instance details
type Apply ((<=@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 <= l2

type (<=@#@$$$) (t :: a6989586621679303258) (t :: a6989586621679303258) = (<=) t t Source #

data (>@#@$) (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type)) Source #

Instances
SuppressUnusedWarnings ((>@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
type Apply ((>@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply ((>@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) = (>@#@$$) l

data (l :: a6989586621679303258) >@#@$$ (l :: TyFun a6989586621679303258 Bool) Source #

Instances
SuppressUnusedWarnings ((>@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
type Apply ((>@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) Source # 
Instance details
type Apply ((>@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 > l2

type (>@#@$$$) (t :: a6989586621679303258) (t :: a6989586621679303258) = (>) t t Source #

data (>=@#@$) (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type)) Source #

Instances
SuppressUnusedWarnings ((>=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) Source # 
Instance details
type Apply ((>=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply ((>=@#@$) :: TyFun a6989586621679303258 (TyFun a6989586621679303258 Bool -> Type) -> *) (l :: a6989586621679303258) = (>=@#@$$) l

data (l :: a6989586621679303258) >=@#@$$ (l :: TyFun a6989586621679303258 Bool) Source #

Instances
SuppressUnusedWarnings ((>=@#@$$) :: a6989586621679303258 -> TyFun a6989586621679303258 Bool -> *) Source # 
Instance details
type Apply ((>=@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) Source # 
Instance details
type Apply ((>=@#@$$) l1 :: TyFun a Bool -> *) (l2 :: a) = l1 >= l2

type (>=@#@$$$) (t :: a6989586621679303258) (t :: a6989586621679303258) = (>=) t t Source #

data MaxSym0 (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type)) Source #

Instances
SuppressUnusedWarnings (MaxSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) Source # 
Instance details
type Apply (MaxSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply (MaxSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) (l :: a6989586621679303258) = MaxSym1 l

data MaxSym1 (l :: a6989586621679303258) (l :: TyFun a6989586621679303258 a6989586621679303258) Source #

Instances
SuppressUnusedWarnings (MaxSym1 :: a6989586621679303258 -> TyFun a6989586621679303258 a6989586621679303258 -> *) Source # 
Instance details
type Apply (MaxSym1 l1 :: TyFun a a -> *) (l2 :: a) Source # 
Instance details
type Apply (MaxSym1 l1 :: TyFun a a -> *) (l2 :: a) = Max l1 l2

type MaxSym2 (t :: a6989586621679303258) (t :: a6989586621679303258) = Max t t Source #

data MinSym0 (l :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type)) Source #

Instances
SuppressUnusedWarnings (MinSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) Source # 
Instance details
type Apply (MinSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) (l :: a6989586621679303258) Source # 
Instance details
type Apply (MinSym0 :: TyFun a6989586621679303258 (TyFun a6989586621679303258 a6989586621679303258 -> Type) -> *) (l :: a6989586621679303258) = MinSym1 l

data MinSym1 (l :: a6989586621679303258) (l :: TyFun a6989586621679303258 a6989586621679303258) Source #

Instances
SuppressUnusedWarnings (MinSym1 :: a6989586621679303258 -> TyFun a6989586621679303258 a6989586621679303258 -> *) Source # 
Instance details
type Apply (MinSym1 l1 :: TyFun a a -> *) (l2 :: a) Source # 
Instance details
type Apply (MinSym1 l1 :: TyFun a a -> *) (l2 :: a) = Min l1 l2

type MinSym2 (t :: a6989586621679303258) (t :: a6989586621679303258) = Min t t Source #

data ComparingSym0 (l :: TyFun (TyFun b6989586621679303248 a6989586621679303247 -> Type) (TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> Type)) Source #

Instances
SuppressUnusedWarnings (ComparingSym0 :: TyFun (TyFun b6989586621679303248 a6989586621679303247 -> Type) (TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> Type) -> *) Source # 
Instance details
type Apply (ComparingSym0 :: TyFun (TyFun b6989586621679303248 a6989586621679303247 -> Type) (TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> Type) -> *) (l :: TyFun b6989586621679303248 a6989586621679303247 -> Type) Source # 
Instance details
type Apply (ComparingSym0 :: TyFun (TyFun b6989586621679303248 a6989586621679303247 -> Type) (TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> Type) -> *) (l :: TyFun b6989586621679303248 a6989586621679303247 -> Type) = ComparingSym1 l

data ComparingSym1 (l :: TyFun b6989586621679303248 a6989586621679303247 -> Type) (l :: TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type)) Source #

Instances
SuppressUnusedWarnings (ComparingSym1 :: (TyFun b6989586621679303248 a6989586621679303247 -> Type) -> TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> *) Source # 
Instance details
type Apply (ComparingSym1 l1 :: TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> *) (l2 :: b6989586621679303248) Source # 
Instance details
type Apply (ComparingSym1 l1 :: TyFun b6989586621679303248 (TyFun b6989586621679303248 Ordering -> Type) -> *) (l2 :: b6989586621679303248) = ComparingSym2 l1 l2

data ComparingSym2 (l :: TyFun b6989586621679303248 a6989586621679303247 -> Type) (l :: b6989586621679303248) (l :: TyFun b6989586621679303248 Ordering) Source #

Instances
SuppressUnusedWarnings (ComparingSym2 :: (TyFun b6989586621679303248 a6989586621679303247 -> Type) -> b6989586621679303248 -> TyFun b6989586621679303248 Ordering -> *) Source # 
Instance details
type Apply (ComparingSym2 l1 l2 :: TyFun b Ordering -> *) (l3 :: b) Source # 
Instance details
type Apply (ComparingSym2 l1 l2 :: TyFun b Ordering -> *) (l3 :: b) = Comparing l1 l2 l3

type ComparingSym3 (t :: TyFun b6989586621679303248 a6989586621679303247 -> Type) (t :: b6989586621679303248) (t :: b6989586621679303248) = Comparing t t t Source #