singletons-2.2: 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 (Proxy :: Proxy a), kproxy ~ Proxy) => POrd kproxy 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 (Proxy * Bool) Source # 

Associated Types

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

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

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

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

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

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

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

POrd Ordering (Proxy * Ordering) Source # 

Associated Types

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

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

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

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

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

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

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

POrd () (Proxy * ()) Source # 

Associated Types

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

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

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

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

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

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

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

POrd [a0] (Proxy * [a0]) Source # 

Associated Types

type Compare (Proxy * [a0]) (arg :: Proxy * [a0]) (arg :: Proxy * [a0]) :: Ordering Source #

type ((Proxy * [a0]) :< (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool Source #

type ((Proxy * [a0]) :<= (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool Source #

type ((Proxy * [a0]) :> (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool Source #

type ((Proxy * [a0]) :>= (arg :: Proxy * [a0])) (arg :: Proxy * [a0]) :: Bool Source #

type Max (Proxy * [a0]) (arg :: Proxy * [a0]) (arg :: Proxy * [a0]) :: a Source #

type Min (Proxy * [a0]) (arg :: Proxy * [a0]) (arg :: Proxy * [a0]) :: a Source #

POrd (Maybe a0) (Proxy * (Maybe a0)) Source # 

Associated Types

type Compare (Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) :: Ordering Source #

type ((Proxy * (Maybe a0)) :< (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool Source #

type ((Proxy * (Maybe a0)) :<= (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool Source #

type ((Proxy * (Maybe a0)) :> (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool Source #

type ((Proxy * (Maybe a0)) :>= (arg :: Proxy * (Maybe a0))) (arg :: Proxy * (Maybe a0)) :: Bool Source #

type Max (Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) :: a Source #

type Min (Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) (arg :: Proxy * (Maybe a0)) :: a Source #

POrd (NonEmpty a0) (Proxy * (NonEmpty a0)) Source # 

Associated Types

type Compare (Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) :: Ordering Source #

type ((Proxy * (NonEmpty a0)) :< (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool Source #

type ((Proxy * (NonEmpty a0)) :<= (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool Source #

type ((Proxy * (NonEmpty a0)) :> (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool Source #

type ((Proxy * (NonEmpty a0)) :>= (arg :: Proxy * (NonEmpty a0))) (arg :: Proxy * (NonEmpty a0)) :: Bool Source #

type Max (Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) :: a Source #

type Min (Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) (arg :: Proxy * (NonEmpty a0)) :: a Source #

POrd (Either a0 b0) (Proxy * (Either a0 b0)) Source # 

Associated Types

type Compare (Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) :: Ordering Source #

type ((Proxy * (Either a0 b0)) :< (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool Source #

type ((Proxy * (Either a0 b0)) :<= (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool Source #

type ((Proxy * (Either a0 b0)) :> (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool Source #

type ((Proxy * (Either a0 b0)) :>= (arg :: Proxy * (Either a0 b0))) (arg :: Proxy * (Either a0 b0)) :: Bool Source #

type Max (Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) :: a Source #

type Min (Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) (arg :: Proxy * (Either a0 b0)) :: a Source #

POrd (a0, b0) (Proxy * (a0, b0)) Source # 

Associated Types

type Compare (Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) :: Ordering Source #

type ((Proxy * (a0, b0)) :< (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool Source #

type ((Proxy * (a0, b0)) :<= (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool Source #

type ((Proxy * (a0, b0)) :> (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool Source #

type ((Proxy * (a0, b0)) :>= (arg :: Proxy * (a0, b0))) (arg :: Proxy * (a0, b0)) :: Bool Source #

type Max (Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) :: a Source #

type Min (Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) (arg :: Proxy * (a0, b0)) :: a Source #

POrd (a0, b0, c0) (Proxy * (a0, b0, c0)) Source # 

Associated Types

type Compare (Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) :: Ordering Source #

type ((Proxy * (a0, b0, c0)) :< (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool Source #

type ((Proxy * (a0, b0, c0)) :<= (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool Source #

type ((Proxy * (a0, b0, c0)) :> (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool Source #

type ((Proxy * (a0, b0, c0)) :>= (arg :: Proxy * (a0, b0, c0))) (arg :: Proxy * (a0, b0, c0)) :: Bool Source #

type Max (Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) :: a Source #

type Min (Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) (arg :: Proxy * (a0, b0, c0)) :: a Source #

POrd (a0, b0, c0, d0) (Proxy * (a0, b0, c0, d0)) Source # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) :: Ordering Source #

type ((Proxy * (a0, b0, c0, d0)) :< (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0)) :<= (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0)) :> (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0)) :>= (arg :: Proxy * (a0, b0, c0, d0))) (arg :: Proxy * (a0, b0, c0, d0)) :: Bool Source #

type Max (Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) :: a Source #

type Min (Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) (arg :: Proxy * (a0, b0, c0, d0)) :: a Source #

POrd (a0, b0, c0, d0, e0) (Proxy * (a0, b0, c0, d0, e0)) Source # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Ordering Source #

type ((Proxy * (a0, b0, c0, d0, e0)) :< (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0)) :<= (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0)) :> (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0)) :>= (arg :: Proxy * (a0, b0, c0, d0, e0))) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: Bool Source #

type Max (Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: a Source #

type Min (Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) (arg :: Proxy * (a0, b0, c0, d0, e0)) :: a Source #

POrd (a0, b0, c0, d0, e0, f0) (Proxy * (a0, b0, c0, d0, e0, f0)) Source # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Ordering Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :< (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :<= (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :> (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0)) :>= (arg :: Proxy * (a0, b0, c0, d0, e0, f0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: Bool Source #

type Max (Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: a Source #

type Min (Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0)) :: a Source #

POrd (a0, b0, c0, d0, e0, f0, g0) (Proxy * (a0, b0, c0, d0, e0, f0, g0)) Source # 

Associated Types

type Compare (Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Ordering Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :< (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :<= (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :> (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool Source #

type ((Proxy * (a0, b0, c0, d0, e0, f0, g0)) :>= (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0))) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: Bool Source #

type Max (Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: a Source #

type Min (Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) (arg :: Proxy * (a0, b0, c0, d0, e0, f0, g0)) :: a Source #

type LTSym0 = LT Source #

type EQSym0 = EQ Source #

type GTSym0 = GT Source #

data CompareSym0 l Source #

Instances

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

Methods

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

type Apply a1627682221 (TyFun a1627682221 Ordering -> Type) (CompareSym0 a1627682221) l0 Source # 
type Apply a1627682221 (TyFun a1627682221 Ordering -> Type) (CompareSym0 a1627682221) l0 = CompareSym1 a1627682221 l0

data CompareSym1 l l Source #

Instances

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

Methods

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

type Apply a1627682221 Ordering (CompareSym1 a1627682221 l1) l0 Source # 
type Apply a1627682221 Ordering (CompareSym1 a1627682221 l1) l0 = CompareSym2 a1627682221 l1 l0

type CompareSym2 t t = Compare t t Source #

data (:<$) l Source #

Instances

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

Methods

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

type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:<$) a1627682221) l0 Source # 
type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:<$) a1627682221) l0 = (:<$$) a1627682221 l0

data l :<$$ l Source #

Instances

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

Methods

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

type Apply a1627682221 Bool ((:<$$) a1627682221 l1) l0 Source # 
type Apply a1627682221 Bool ((:<$$) a1627682221 l1) l0 = (:<$$$) a1627682221 l1 l0

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

data (:<=$) l Source #

Instances

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

Methods

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

type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:<=$) a1627682221) l0 Source # 
type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:<=$) a1627682221) l0 = (:<=$$) a1627682221 l0

data l :<=$$ l Source #

Instances

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

Methods

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

type Apply a1627682221 Bool ((:<=$$) a1627682221 l1) l0 Source # 
type Apply a1627682221 Bool ((:<=$$) a1627682221 l1) l0 = (:<=$$$) a1627682221 l1 l0

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

data (:>$) l Source #

Instances

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

Methods

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

type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:>$) a1627682221) l0 Source # 
type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:>$) a1627682221) l0 = (:>$$) a1627682221 l0

data l :>$$ l Source #

Instances

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

Methods

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

type Apply a1627682221 Bool ((:>$$) a1627682221 l1) l0 Source # 
type Apply a1627682221 Bool ((:>$$) a1627682221 l1) l0 = (:>$$$) a1627682221 l1 l0

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

data (:>=$) l Source #

Instances

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

Methods

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

type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:>=$) a1627682221) l0 Source # 
type Apply a1627682221 (TyFun a1627682221 Bool -> Type) ((:>=$) a1627682221) l0 = (:>=$$) a1627682221 l0

data l :>=$$ l Source #

Instances

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

Methods

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

type Apply a1627682221 Bool ((:>=$$) a1627682221 l1) l0 Source # 
type Apply a1627682221 Bool ((:>=$$) a1627682221 l1) l0 = (:>=$$$) a1627682221 l1 l0

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

data MaxSym0 l Source #

Instances

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

Methods

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

type Apply a1627682221 (TyFun a1627682221 a1627682221 -> Type) (MaxSym0 a1627682221) l0 Source # 
type Apply a1627682221 (TyFun a1627682221 a1627682221 -> Type) (MaxSym0 a1627682221) l0 = MaxSym1 a1627682221 l0

data MaxSym1 l l Source #

Instances

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

Methods

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

type Apply a1627682221 a1627682221 (MaxSym1 a1627682221 l1) l0 Source # 
type Apply a1627682221 a1627682221 (MaxSym1 a1627682221 l1) l0 = MaxSym2 a1627682221 l1 l0

type MaxSym2 t t = Max t t Source #

data MinSym0 l Source #

Instances

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

Methods

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

type Apply a1627682221 (TyFun a1627682221 a1627682221 -> Type) (MinSym0 a1627682221) l0 Source # 
type Apply a1627682221 (TyFun a1627682221 a1627682221 -> Type) (MinSym0 a1627682221) l0 = MinSym1 a1627682221 l0

data MinSym1 l l Source #

Instances

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

Methods

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

type Apply a1627682221 a1627682221 (MinSym1 a1627682221 l1) l0 Source # 
type Apply a1627682221 a1627682221 (MinSym1 a1627682221 l1) l0 = MinSym2 a1627682221 l1 l0

type MinSym2 t t = Min t t Source #