singletons-2.3.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 a => POrd (a :: Type) Source #

Associated Types

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

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

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

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

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

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

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

Instances

POrd Bool Source # 

Associated Types

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

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

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

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

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

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

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

POrd Ordering Source # 

Associated Types

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

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

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

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

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

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

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

POrd () 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 #

POrd [a] Source # 

Associated Types

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

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

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

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

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

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

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

POrd (Maybe a) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (NonEmpty a) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (Either a b) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (a, b) Source # 

Associated Types

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

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

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

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

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

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

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

POrd (a, b, c) Source # 

Associated Types

type Compare (a, b, c) (arg :: (a, b, c)) (arg :: (a, b, c)) :: Ordering Source #

type ((a, b, c) :< (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type ((a, b, c) :<= (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type ((a, b, c) :> (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type ((a, b, c) :>= (arg :: (a, b, c))) (arg :: (a, b, c)) :: Bool Source #

type Max (a, b, c) (arg :: (a, b, c)) (arg :: (a, b, c)) :: a Source #

type Min (a, b, c) (arg :: (a, b, c)) (arg :: (a, b, c)) :: a Source #

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

Associated Types

type Compare (a, b, c, d) (arg :: (a, b, c, d)) (arg :: (a, b, c, d)) :: Ordering Source #

type ((a, b, c, d) :< (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type ((a, b, c, d) :<= (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type ((a, b, c, d) :> (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type ((a, b, c, d) :>= (arg :: (a, b, c, d))) (arg :: (a, b, c, d)) :: Bool Source #

type Max (a, b, c, d) (arg :: (a, b, c, d)) (arg :: (a, b, c, d)) :: a Source #

type Min (a, b, c, d) (arg :: (a, b, c, d)) (arg :: (a, b, c, d)) :: a Source #

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

Associated Types

type Compare (a, b, c, d, e) (arg :: (a, b, c, d, e)) (arg :: (a, b, c, d, e)) :: Ordering Source #

type ((a, b, c, d, e) :< (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type ((a, b, c, d, e) :<= (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type ((a, b, c, d, e) :> (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type ((a, b, c, d, e) :>= (arg :: (a, b, c, d, e))) (arg :: (a, b, c, d, e)) :: Bool Source #

type Max (a, b, c, d, e) (arg :: (a, b, c, d, e)) (arg :: (a, b, c, d, e)) :: a Source #

type Min (a, b, c, d, e) (arg :: (a, b, c, d, e)) (arg :: (a, b, c, d, e)) :: a Source #

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

Associated Types

type Compare (a, b, c, d, e, f) (arg :: (a, b, c, d, e, f)) (arg :: (a, b, c, d, e, f)) :: Ordering Source #

type ((a, b, c, d, e, f) :< (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type ((a, b, c, d, e, f) :<= (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type ((a, b, c, d, e, f) :> (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type ((a, b, c, d, e, f) :>= (arg :: (a, b, c, d, e, f))) (arg :: (a, b, c, d, e, f)) :: Bool Source #

type Max (a, b, c, d, e, f) (arg :: (a, b, c, d, e, f)) (arg :: (a, b, c, d, e, f)) :: a Source #

type Min (a, b, c, d, e, f) (arg :: (a, b, c, d, e, f)) (arg :: (a, b, c, d, e, f)) :: a Source #

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

Associated Types

type Compare (a, b, c, d, e, f, g) (arg :: (a, b, c, d, e, f, g)) (arg :: (a, b, c, d, e, f, g)) :: Ordering Source #

type ((a, b, c, d, e, f, g) :< (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type ((a, b, c, d, e, f, g) :<= (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type ((a, b, c, d, e, f, g) :> (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type ((a, b, c, d, e, f, g) :>= (arg :: (a, b, c, d, e, f, g))) (arg :: (a, b, c, d, e, f, g)) :: Bool Source #

type Max (a, b, c, d, e, f, g) (arg :: (a, b, c, d, e, f, g)) (arg :: (a, b, c, d, e, f, g)) :: a Source #

type Min (a, b, c, d, e, f, g) (arg :: (a, b, c, d, e, f, g)) (arg :: (a, b, c, d, e, f, g)) :: a Source #

type LTSym0 = LT Source #

type EQSym0 = EQ Source #

type GTSym0 = GT Source #

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679312550 (TyFun a6989586621679312550 Ordering -> Type) -> *) (CompareSym0 a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym0 a6989586621679312550) t -> () Source #

type Apply a6989586621679312550 (TyFun a6989586621679312550 Ordering -> Type) (CompareSym0 a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 Ordering -> Type) (CompareSym0 a6989586621679312550) l = CompareSym1 a6989586621679312550 l

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

Instances

SuppressUnusedWarnings (a6989586621679312550 -> TyFun a6989586621679312550 Ordering -> *) (CompareSym1 a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy (CompareSym1 a6989586621679312550) t -> () Source #

type Apply a Ordering (CompareSym1 a l1) l2 Source # 
type Apply a Ordering (CompareSym1 a l1) l2 = Compare a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) -> *) ((:<$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:<$) a6989586621679312550) t -> () Source #

type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:<$) a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:<$) a6989586621679312550) l = (:<$$) a6989586621679312550 l

data (l :: a6989586621679312550) :<$$ (l :: TyFun a6989586621679312550 Bool) Source #

Instances

SuppressUnusedWarnings (a6989586621679312550 -> TyFun a6989586621679312550 Bool -> *) ((:<$$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:<$$) a6989586621679312550) t -> () Source #

type Apply a Bool ((:<$$) a l1) l2 Source # 
type Apply a Bool ((:<$$) a l1) l2 = (:<) a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) -> *) ((:<=$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:<=$) a6989586621679312550) t -> () Source #

type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:<=$) a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:<=$) a6989586621679312550) l = (:<=$$) a6989586621679312550 l

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

Instances

SuppressUnusedWarnings (a6989586621679312550 -> TyFun a6989586621679312550 Bool -> *) ((:<=$$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:<=$$) a6989586621679312550) t -> () Source #

type Apply a Bool ((:<=$$) a l1) l2 Source # 
type Apply a Bool ((:<=$$) a l1) l2 = (:<=) a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) -> *) ((:>$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:>$) a6989586621679312550) t -> () Source #

type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:>$) a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:>$) a6989586621679312550) l = (:>$$) a6989586621679312550 l

data (l :: a6989586621679312550) :>$$ (l :: TyFun a6989586621679312550 Bool) Source #

Instances

SuppressUnusedWarnings (a6989586621679312550 -> TyFun a6989586621679312550 Bool -> *) ((:>$$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:>$$) a6989586621679312550) t -> () Source #

type Apply a Bool ((:>$$) a l1) l2 Source # 
type Apply a Bool ((:>$$) a l1) l2 = (:>) a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) -> *) ((:>=$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:>=$) a6989586621679312550) t -> () Source #

type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:>=$) a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 Bool -> Type) ((:>=$) a6989586621679312550) l = (:>=$$) a6989586621679312550 l

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

Instances

SuppressUnusedWarnings (a6989586621679312550 -> TyFun a6989586621679312550 Bool -> *) ((:>=$$) a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:>=$$) a6989586621679312550) t -> () Source #

type Apply a Bool ((:>=$$) a l1) l2 Source # 
type Apply a Bool ((:>=$$) a l1) l2 = (:>=) a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679312550 (TyFun a6989586621679312550 a6989586621679312550 -> Type) -> *) (MaxSym0 a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy (MaxSym0 a6989586621679312550) t -> () Source #

type Apply a6989586621679312550 (TyFun a6989586621679312550 a6989586621679312550 -> Type) (MaxSym0 a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 a6989586621679312550 -> Type) (MaxSym0 a6989586621679312550) l = MaxSym1 a6989586621679312550 l

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

Instances

SuppressUnusedWarnings (a6989586621679312550 -> TyFun a6989586621679312550 a6989586621679312550 -> *) (MaxSym1 a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy (MaxSym1 a6989586621679312550) t -> () Source #

type Apply a a (MaxSym1 a l1) l2 Source # 
type Apply a a (MaxSym1 a l1) l2 = Max a l1 l2

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

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

Instances

SuppressUnusedWarnings (TyFun a6989586621679312550 (TyFun a6989586621679312550 a6989586621679312550 -> Type) -> *) (MinSym0 a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy (MinSym0 a6989586621679312550) t -> () Source #

type Apply a6989586621679312550 (TyFun a6989586621679312550 a6989586621679312550 -> Type) (MinSym0 a6989586621679312550) l Source # 
type Apply a6989586621679312550 (TyFun a6989586621679312550 a6989586621679312550 -> Type) (MinSym0 a6989586621679312550) l = MinSym1 a6989586621679312550 l

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

Instances

SuppressUnusedWarnings (a6989586621679312550 -> TyFun a6989586621679312550 a6989586621679312550 -> *) (MinSym1 a6989586621679312550) Source # 

Methods

suppressUnusedWarnings :: Proxy (MinSym1 a6989586621679312550) t -> () Source #

type Apply a a (MinSym1 a l1) l2 Source # 
type Apply a a (MinSym1 a l1) l2 = Min a l1 l2

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