tfp-1.0.2: Type-level integers, booleans, lists using type families
Safe HaskellSafe-Inferred
LanguageHaskell2010

Type.Data.Ord

Documentation

type family Compare x y Source #

Instances

Instances details
type Compare False False Source # 
Instance details

Defined in Type.Data.Ord

type Compare False True Source # 
Instance details

Defined in Type.Data.Ord

type Compare True False Source # 
Instance details

Defined in Type.Data.Ord

type Compare True True Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT GT = EQ
type Compare GT EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT EQ = GT
type Compare GT LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT LT = GT
type Compare EQ GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ GT = LT
type Compare EQ EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ EQ = EQ
type Compare EQ LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ LT = GT
type Compare LT GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT GT = LT
type Compare LT EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT EQ = LT
type Compare LT LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT LT = EQ
type Compare (Dec x) (Dec y) Source # 
Instance details

Defined in Type.Data.Num.Decimal.Number

type Compare (Dec x) (Dec y) = Compare x y

compare :: Proxy x -> Proxy y -> Proxy (Compare x y) Source #

data LT Source #

Instances

Instances details
type IsGT LT Source # 
Instance details

Defined in Type.Data.Ord

type IsGT LT = False
type IsEQ LT Source # 
Instance details

Defined in Type.Data.Ord

type IsEQ LT = False
type IsLT LT Source # 
Instance details

Defined in Type.Data.Ord

type IsLT LT = True
type Compare GT LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT LT = GT
type Compare EQ LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ LT = GT
type Compare LT GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT GT = LT
type Compare LT EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT EQ = LT
type Compare LT LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT LT = EQ

data EQ Source #

Instances

Instances details
type IsGT EQ Source # 
Instance details

Defined in Type.Data.Ord

type IsGT EQ = False
type IsEQ EQ Source # 
Instance details

Defined in Type.Data.Ord

type IsEQ EQ = True
type IsLT EQ Source # 
Instance details

Defined in Type.Data.Ord

type IsLT EQ = False
type Compare GT EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT EQ = GT
type Compare EQ GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ GT = LT
type Compare EQ EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ EQ = EQ
type Compare EQ LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ LT = GT
type Compare LT EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT EQ = LT

data GT Source #

Instances

Instances details
type IsGT GT Source # 
Instance details

Defined in Type.Data.Ord

type IsGT GT = True
type IsEQ GT Source # 
Instance details

Defined in Type.Data.Ord

type IsEQ GT = False
type IsLT GT Source # 
Instance details

Defined in Type.Data.Ord

type IsLT GT = False
type Compare GT GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT GT = EQ
type Compare GT EQ Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT EQ = GT
type Compare GT LT Source # 
Instance details

Defined in Type.Data.Ord

type Compare GT LT = GT
type Compare EQ GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare EQ GT = LT
type Compare LT GT Source # 
Instance details

Defined in Type.Data.Ord

type Compare LT GT = LT

type family IsLT c Source #

Instances

Instances details
type IsLT GT Source # 
Instance details

Defined in Type.Data.Ord

type IsLT GT = False
type IsLT EQ Source # 
Instance details

Defined in Type.Data.Ord

type IsLT EQ = False
type IsLT LT Source # 
Instance details

Defined in Type.Data.Ord

type IsLT LT = True

isLT :: Proxy c -> Proxy (IsLT c) Source #

type family IsEQ c Source #

Instances

Instances details
type IsEQ GT Source # 
Instance details

Defined in Type.Data.Ord

type IsEQ GT = False
type IsEQ EQ Source # 
Instance details

Defined in Type.Data.Ord

type IsEQ EQ = True
type IsEQ LT Source # 
Instance details

Defined in Type.Data.Ord

type IsEQ LT = False

isEQ :: Proxy c -> Proxy (IsEQ c) Source #

type family IsGT c Source #

Instances

Instances details
type IsGT GT Source # 
Instance details

Defined in Type.Data.Ord

type IsGT GT = True
type IsGT EQ Source # 
Instance details

Defined in Type.Data.Ord

type IsGT EQ = False
type IsGT LT Source # 
Instance details

Defined in Type.Data.Ord

type IsGT LT = False

isGT :: Proxy c -> Proxy (IsGT c) Source #

class x :<: y Source #

lt :: Proxy x -> Proxy y -> Proxy (LTT x y) Source #

type family LTT x y Source #

Instances

Instances details
type LTT x y Source # 
Instance details

Defined in Type.Data.Ord

type LTT x y = IsLT (Compare x y)

class x :<=: y Source #

le :: Proxy x -> Proxy y -> Proxy (LET x y) Source #

type family LET x y Source #

Instances

Instances details
type LET x y Source # 
Instance details

Defined in Type.Data.Ord

type LET x y = Not (GTT x y)

class x :==: y Source #

eq :: Proxy x -> Proxy y -> Proxy (EQT x y) Source #

type family EQT x y Source #

Instances

Instances details
type EQT x y Source # 
Instance details

Defined in Type.Data.Ord

type EQT x y = IsEQ (Compare x y)

class x :/=: y Source #

ne :: Proxy x -> Proxy y -> Proxy (NET x y) Source #

type family NET x y Source #

Instances

Instances details
type NET x y Source # 
Instance details

Defined in Type.Data.Ord

type NET x y = Not (EQT x y)

class x :>=: y Source #

ge :: Proxy x -> Proxy y -> Proxy (GET x y) Source #

type family GET x y Source #

Instances

Instances details
type GET x y Source # 
Instance details

Defined in Type.Data.Ord

type GET x y = Not (LTT x y)

class x :>: y Source #

gt :: Proxy x -> Proxy y -> Proxy (GTT x y) Source #

type family GTT x y Source #

Instances

Instances details
type GTT x y Source # 
Instance details

Defined in Type.Data.Ord

type GTT x y = IsGT (Compare x y)

type family Min x y Source #

Instances

Instances details
type Min x y Source # 
Instance details

Defined in Type.Data.Ord

type Min x y = If (LET x y) x y

min :: Proxy x -> Proxy y -> Proxy (Min x y) Source #

type family Max x y Source #

Instances

Instances details
type Max x y Source # 
Instance details

Defined in Type.Data.Ord

type Max x y = If (GET x y) x y

max :: Proxy x -> Proxy y -> Proxy (Max x y) Source #