singletons-1.1.1: 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

Description

Provides promoted definitions related to type-level comparisons.

Documentation

class (PEq (KProxy :: KProxy a), kproxy ~ KProxy) => POrd kproxy Source

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

Instances

POrd Bool (KProxy Bool) 
POrd Ordering (KProxy Ordering) 
POrd Nat (KProxy Nat) 
POrd Symbol (KProxy Symbol) 
POrd () (KProxy ()) 
POrd [k] (KProxy [k]) 
POrd (Maybe k) (KProxy (Maybe k)) 
POrd (Either k k) (KProxy (Either k k)) 
POrd ((,) k k) (KProxy ((,) k k)) 
POrd ((,,) k k k) (KProxy ((,,) k k k)) 
POrd ((,,,) k k k k) (KProxy ((,,,) k k k k)) 
POrd ((,,,,) k k k k k) (KProxy ((,,,,) k k k k k)) 
POrd ((,,,,,) k k k k k k) (KProxy ((,,,,,) k k k k k k)) 
POrd ((,,,,,,) k k k k k k k) (KProxy ((,,,,,,) k k k k k k k)) 

data CompareSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k Ordering -> *) -> *) (CompareSym0 k) 
type Apply (TyFun k Ordering -> *) k (CompareSym0 k) l0 = CompareSym1 k l0 

data CompareSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun k Ordering -> *) (CompareSym1 k) 
type Apply Ordering k (CompareSym1 k l1) l0 = CompareSym2 k l1 l0 

type CompareSym2 t t = Compare t t Source

data (:<$) l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k Bool -> *) -> *) ((:<$) k) 
type Apply (TyFun k Bool -> *) k ((:<$) k) l0 = (:<$$) k l0 

data l :<$$ l Source

Instances

SuppressUnusedWarnings (k -> TyFun k Bool -> *) ((:<$$) k) 
type Apply Bool k ((:<$$) k l1) l0 = (:<$$$) k l1 l0 

type (:<$$$) t t = (:<) t t Source

data (:<=$) l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k Bool -> *) -> *) ((:<=$) k) 
type Apply (TyFun k Bool -> *) k ((:<=$) k) l0 = (:<=$$) k l0 

data l :<=$$ l Source

Instances

SuppressUnusedWarnings (k -> TyFun k Bool -> *) ((:<=$$) k) 
type Apply Bool k ((:<=$$) k l1) l0 = (:<=$$$) k l1 l0 

type (:<=$$$) t t = (:<=) t t Source

data (:>$) l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k Bool -> *) -> *) ((:>$) k) 
type Apply (TyFun k Bool -> *) k ((:>$) k) l0 = (:>$$) k l0 

data l :>$$ l Source

Instances

SuppressUnusedWarnings (k -> TyFun k Bool -> *) ((:>$$) k) 
type Apply Bool k ((:>$$) k l1) l0 = (:>$$$) k l1 l0 

type (:>$$$) t t = (:>) t t Source

data (:>=$) l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k Bool -> *) -> *) ((:>=$) k) 
type Apply (TyFun k Bool -> *) k ((:>=$) k) l0 = (:>=$$) k l0 

data l :>=$$ l Source

Instances

SuppressUnusedWarnings (k -> TyFun k Bool -> *) ((:>=$$) k) 
type Apply Bool k ((:>=$$) k l1) l0 = (:>=$$$) k l1 l0 

type (:>=$$$) t t = (:>=) t t Source

data MaxSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k k -> *) -> *) (MaxSym0 k) 
type Apply (TyFun k k -> *) k (MaxSym0 k) l0 = MaxSym1 k l0 

data MaxSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun k k -> *) (MaxSym1 k) 
type Apply k k (MaxSym1 k l1) l0 = MaxSym2 k l1 l0 

type MaxSym2 t t = Max t t Source

data MinSym0 l Source

Instances

SuppressUnusedWarnings (TyFun k (TyFun k k -> *) -> *) (MinSym0 k) 
type Apply (TyFun k k -> *) k (MinSym0 k) l0 = MinSym1 k l0 

data MinSym1 l l Source

Instances

SuppressUnusedWarnings (k -> TyFun k k -> *) (MinSym1 k) 
type Apply k k (MinSym1 k l1) l0 = MinSym2 k l1 l0 

type MinSym2 t t = Min t t Source