Copyright | (C) 2013 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- class POrd a where
- class SEq a => SOrd a where
- sCompare :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering)
- (%<) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t :: Bool)
- (%<=) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t :: Bool)
- (%>) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t :: Bool)
- (%>=) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t :: Bool)
- sMax :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t :: a)
- sMin :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t :: a)
- type family Comparing (a :: (~>) b a) (a :: b) (a :: b) :: Ordering where ...
- sComparing :: forall b a (t :: (~>) b a) (t :: b) (t :: b). SOrd a => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ComparingSym0 t) t) t :: Ordering)
- thenCmp :: Ordering -> Ordering -> Ordering
- type family ThenCmp (a :: Ordering) (a :: Ordering) :: Ordering where ...
- sThenCmp :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply ThenCmpSym0 t) t :: Ordering)
- type family Sing :: k -> Type
- data SOrdering :: Ordering -> Type where
- data SDown :: forall (a :: Type). Down a -> Type where
- type family GetDown (a :: Down (a :: Type)) :: a where ...
- sGetDown :: forall (a :: Type) (t :: Down (a :: Type)). Sing t -> Sing (Apply GetDownSym0 t :: a)
- data ThenCmpSym0 :: (~>) Ordering ((~>) Ordering Ordering)
- data ThenCmpSym1 (a6989586621679184996 :: Ordering) :: (~>) Ordering Ordering
- type family ThenCmpSym2 (a6989586621679184996 :: Ordering) (a6989586621679184997 :: Ordering) :: Ordering where ...
- type family LTSym0 :: Ordering where ...
- type family EQSym0 :: Ordering where ...
- type family GTSym0 :: Ordering where ...
- data CompareSym0 :: (~>) a ((~>) a Ordering)
- data CompareSym1 (a6989586621679185012 :: a) :: (~>) a Ordering
- type family CompareSym2 (a6989586621679185012 :: a) (a6989586621679185013 :: a) :: Ordering where ...
- data (<@#@$) :: (~>) a ((~>) a Bool)
- data (<@#@$$) (a6989586621679185017 :: a) :: (~>) a Bool
- type family (a6989586621679185017 :: a) <@#@$$$ (a6989586621679185018 :: a) :: Bool where ...
- data (<=@#@$) :: (~>) a ((~>) a Bool)
- data (<=@#@$$) (a6989586621679185022 :: a) :: (~>) a Bool
- type family (a6989586621679185022 :: a) <=@#@$$$ (a6989586621679185023 :: a) :: Bool where ...
- data (>@#@$) :: (~>) a ((~>) a Bool)
- data (>@#@$$) (a6989586621679185027 :: a) :: (~>) a Bool
- type family (a6989586621679185027 :: a) >@#@$$$ (a6989586621679185028 :: a) :: Bool where ...
- data (>=@#@$) :: (~>) a ((~>) a Bool)
- data (>=@#@$$) (a6989586621679185032 :: a) :: (~>) a Bool
- type family (a6989586621679185032 :: a) >=@#@$$$ (a6989586621679185033 :: a) :: Bool where ...
- data MaxSym0 :: (~>) a ((~>) a a)
- data MaxSym1 (a6989586621679185037 :: a) :: (~>) a a
- type family MaxSym2 (a6989586621679185037 :: a) (a6989586621679185038 :: a) :: a where ...
- data MinSym0 :: (~>) a ((~>) a a)
- data MinSym1 (a6989586621679185042 :: a) :: (~>) a a
- type family MinSym2 (a6989586621679185042 :: a) (a6989586621679185043 :: a) :: a where ...
- data ComparingSym0 :: (~>) ((~>) b a) ((~>) b ((~>) b Ordering))
- data ComparingSym1 (a6989586621679185003 :: (~>) b a) :: (~>) b ((~>) b Ordering)
- data ComparingSym2 (a6989586621679185003 :: (~>) b a) (a6989586621679185004 :: b) :: (~>) b Ordering
- type family ComparingSym3 (a6989586621679185003 :: (~>) b a) (a6989586621679185004 :: b) (a6989586621679185005 :: b) :: Ordering where ...
- data DownSym0 :: (~>) a (Down (a :: Type))
- type family DownSym1 (a6989586621679195717 :: a) :: Down (a :: Type) where ...
- data GetDownSym0 :: (~>) (Down (a :: Type)) a
- type family GetDownSym1 (a6989586621679195720 :: Down (a :: Type)) :: a where ...
Documentation
type Compare (arg :: a) (arg :: a) :: Ordering Source #
type Compare a a = Apply (Apply Compare_6989586621679185046Sym0 a) a
type (arg :: a) < (arg :: a) :: Bool infix 4 Source #
type a < a = Apply (Apply TFHelper_6989586621679185067Sym0 a) a
type (arg :: a) <= (arg :: a) :: Bool infix 4 Source #
type a <= a = Apply (Apply TFHelper_6989586621679185083Sym0 a) a
type (arg :: a) > (arg :: a) :: Bool infix 4 Source #
type a > a = Apply (Apply TFHelper_6989586621679185099Sym0 a) a
type (arg :: a) >= (arg :: a) :: Bool infix 4 Source #
type a >= a = Apply (Apply TFHelper_6989586621679185115Sym0 a) a
type Max (arg :: a) (arg :: a) :: a Source #
type Max a a = Apply (Apply Max_6989586621679185131Sym0 a) a
type Min (arg :: a) (arg :: a) :: a Source #
type Min a a = Apply (Apply Min_6989586621679185147Sym0 a) a
Instances
POrd All Source # | |
POrd Any Source # | |
POrd Void Source # | |
POrd Ordering Source # | |
POrd Natural Source # | |
POrd () Source # | |
POrd Bool Source # | |
POrd Char Source # | |
POrd Symbol Source # | |
POrd (Identity a) Source # | |
POrd (First a) Source # | |
POrd (Last a) Source # | |
POrd (Down a) Source # | |
POrd (First a) Source # | |
POrd (Last a) Source # | |
POrd (Max a) Source # | |
POrd (Min a) Source # | |
POrd (WrappedMonoid m) Source # | |
POrd (Dual a) Source # | |
POrd (Product a) Source # | |
POrd (Sum a) Source # | |
POrd (NonEmpty a) Source # | |
POrd (Maybe a) Source # | |
POrd [a] Source # | |
POrd (Either a b) Source # | |
POrd (Proxy s) Source # | |
POrd (Arg a b) Source # | |
POrd (a, b) Source # | |
POrd (Const a b) Source # | |
POrd (a, b, c) Source # | |
POrd (a, b, c, d) Source # | |
POrd (a, b, c, d, e) Source # | |
POrd (a, b, c, d, e, f) Source # | |
POrd (a, b, c, d, e, f, g) Source # | |
class SEq a => SOrd a where Source #
Nothing
sCompare :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering) Source #
default sCompare :: forall (t :: a) (t :: a). (Apply (Apply CompareSym0 t) t :: Ordering) ~ Apply (Apply Compare_6989586621679185046Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering) Source #
(%<) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t :: Bool) infix 4 Source #
default (%<) :: forall (t :: a) (t :: a). (Apply (Apply (<@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679185067Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t :: Bool) Source #
(%<=) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t :: Bool) infix 4 Source #
default (%<=) :: forall (t :: a) (t :: a). (Apply (Apply (<=@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679185083Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t :: Bool) Source #
(%>) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t :: Bool) infix 4 Source #
default (%>) :: forall (t :: a) (t :: a). (Apply (Apply (>@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679185099Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t :: Bool) Source #
(%>=) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t :: Bool) infix 4 Source #
default (%>=) :: forall (t :: a) (t :: a). (Apply (Apply (>=@#@$) t) t :: Bool) ~ Apply (Apply TFHelper_6989586621679185115Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t :: Bool) Source #
sMax :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t :: a) Source #
default sMax :: forall (t :: a) (t :: a). (Apply (Apply MaxSym0 t) t :: a) ~ Apply (Apply Max_6989586621679185131Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t :: a) Source #
sMin :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t :: a) Source #
Instances
SOrd Bool => SOrd All Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Bool => SOrd Any Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Void Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Ordering Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Natural Source # | |
Defined in GHC.TypeLits.Singletons.Internal sCompare :: forall (t :: Natural) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Natural) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Natural) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Natural) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Natural) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Natural) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Natural) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd () Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: ()) (t :: ()). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: ()) (t :: ()). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: ()) (t :: ()). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: ()) (t :: ()). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: ()) (t :: ()). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: ()) (t :: ()). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: ()) (t :: ()). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Bool Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: Bool) (t :: Bool). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Bool) (t :: Bool). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Bool) (t :: Bool). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Bool) (t :: Bool). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Bool) (t :: Bool). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Bool) (t :: Bool). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Bool) (t :: Bool). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Char Source # | |
Defined in GHC.TypeLits.Singletons.Internal sCompare :: forall (t :: Char) (t :: Char). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Char) (t :: Char). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Char) (t :: Char). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Char) (t :: Char). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Char) (t :: Char). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Char) (t :: Char). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Char) (t :: Char). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Symbol Source # | |
Defined in GHC.TypeLits.Singletons.Internal sCompare :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Identity a) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: Identity a) (t :: Identity a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Identity a) (t :: Identity a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Identity a) (t :: Identity a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Identity a) (t :: Identity a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Identity a) (t :: Identity a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Identity a) (t :: Identity a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Identity a) (t :: Identity a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd (Maybe a) => SOrd (First a) Source # | |
Defined in Data.Monoid.Singletons sCompare :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd (Maybe a) => SOrd (Last a) Source # | |
Defined in Data.Monoid.Singletons sCompare :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Down a) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: Down a) (t :: Down a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Down a) (t :: Down a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Down a) (t :: Down a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Down a) (t :: Down a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Down a) (t :: Down a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Down a) (t :: Down a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Down a) (t :: Down a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (First a) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Last a) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Max a) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Min a) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd m => SOrd (WrappedMonoid m) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Dual a) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: Dual a) (t :: Dual a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Dual a) (t :: Dual a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Dual a) (t :: Dual a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Dual a) (t :: Dual a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Dual a) (t :: Dual a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Dual a) (t :: Dual a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Dual a) (t :: Dual a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Product a) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: Product a) (t :: Product a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Product a) (t :: Product a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Product a) (t :: Product a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Product a) (t :: Product a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Product a) (t :: Product a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Product a) (t :: Product a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Product a) (t :: Product a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Sum a) Source # | |
Defined in Data.Semigroup.Singletons.Internal sCompare :: forall (t :: Sum a) (t :: Sum a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Sum a) (t :: Sum a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Sum a) (t :: Sum a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Sum a) (t :: Sum a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Sum a) (t :: Sum a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Sum a) (t :: Sum a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Sum a) (t :: Sum a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd [a]) => SOrd (NonEmpty a) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: NonEmpty a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: NonEmpty a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: NonEmpty a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: NonEmpty a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: NonEmpty a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: NonEmpty a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: NonEmpty a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Maybe a) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: Maybe a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Maybe a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Maybe a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Maybe a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Maybe a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Maybe a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Maybe a) (t :: Maybe a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd [a]) => SOrd [a] Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd b) => SOrd (Either a b) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd (Proxy s) Source # | |
Defined in Data.Proxy.Singletons sCompare :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Proxy s) (t :: Proxy s). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Arg a b) Source # | |
Defined in Data.Semigroup.Singletons sCompare :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd b) => SOrd (a, b) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Const a b) Source # | |
Defined in Data.Functor.Const.Singletons sCompare :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd b, SOrd c) => SOrd (a, b, c) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd b, SOrd c, SOrd d) => SOrd (a, b, c, d) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e) => SOrd (a, b, c, d, e) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e, SOrd f) => SOrd (a, b, c, d, e, f) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: (a, b, c, d, e, f)) (t :: (a, b, c, d, e, f)). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: (a, b, c, d, e, f)) (t :: (a, b, c, d, e, f)). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: (a, b, c, d, e, f)) (t :: (a, b, c, d, e, f)). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: (a, b, c, d, e, f)) (t :: (a, b, c, d, e, f)). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: (a, b, c, d, e, f)) (t :: (a, b, c, d, e, f)). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: (a, b, c, d, e, f)) (t :: (a, b, c, d, e, f)). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: (a, b, c, d, e, f)) (t :: (a, b, c, d, e, f)). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e, SOrd f, SOrd g) => SOrd (a, b, c, d, e, f, g) Source # | |
Defined in Data.Ord.Singletons sCompare :: forall (t :: (a, b, c, d, e, f, g)) (t :: (a, b, c, d, e, f, g)). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: (a, b, c, d, e, f, g)) (t :: (a, b, c, d, e, f, g)). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: (a, b, c, d, e, f, g)) (t :: (a, b, c, d, e, f, g)). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: (a, b, c, d, e, f, g)) (t :: (a, b, c, d, e, f, g)). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: (a, b, c, d, e, f, g)) (t :: (a, b, c, d, e, f, g)). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: (a, b, c, d, e, f, g)) (t :: (a, b, c, d, e, f, g)). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: (a, b, c, d, e, f, g)) (t :: (a, b, c, d, e, f, g)). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # |
type family Comparing (a :: (~>) b a) (a :: b) (a :: b) :: Ordering where ... Source #
Comparing p x y = Apply (Apply CompareSym0 (Apply p x)) (Apply p y) |
sComparing :: forall b a (t :: (~>) b a) (t :: b) (t :: b). SOrd a => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ComparingSym0 t) t) t :: Ordering) Source #
sThenCmp :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply ThenCmpSym0 t) t :: Ordering) Source #
type family Sing :: k -> Type #
Instances
data SOrdering :: Ordering -> Type where Source #
SLT :: SOrdering ('LT :: Ordering) | |
SEQ :: SOrdering ('EQ :: Ordering) | |
SGT :: SOrdering ('GT :: Ordering) |
Instances
TestCoercion SOrdering Source # | |
Defined in Data.Singletons.Base.Instances | |
TestEquality SOrdering Source # | |
Defined in Data.Singletons.Base.Instances | |
Show (SOrdering z) Source # | |
data SDown :: forall (a :: Type). Down a -> Type where Source #
Instances
SDecide a => TestCoercion (SDown :: Down a -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SDecide a => TestEquality (SDown :: Down a -> Type) Source # | |
Defined in Data.Ord.Singletons |
sGetDown :: forall (a :: Type) (t :: Down (a :: Type)). Sing t -> Sing (Apply GetDownSym0 t :: a) Source #
Defunctionalization symbols
data ThenCmpSym0 :: (~>) Ordering ((~>) Ordering Ordering) Source #
Instances
SingI ThenCmpSym0 Source # | |
Defined in Data.Ord.Singletons sing :: Sing ThenCmpSym0 | |
SuppressUnusedWarnings ThenCmpSym0 Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ThenCmpSym0 (a6989586621679184996 :: Ordering) Source # | |
Defined in Data.Ord.Singletons |
data ThenCmpSym1 (a6989586621679184996 :: Ordering) :: (~>) Ordering Ordering Source #
Instances
SingI1 ThenCmpSym1 Source # | |
Defined in Data.Ord.Singletons liftSing :: forall (x :: k1). Sing x -> Sing (ThenCmpSym1 x) | |
SingI d => SingI (ThenCmpSym1 d :: TyFun Ordering Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons sing :: Sing (ThenCmpSym1 d) | |
SuppressUnusedWarnings (ThenCmpSym1 a6989586621679184996 :: TyFun Ordering Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (ThenCmpSym1 a6989586621679184996 :: TyFun Ordering Ordering -> Type) (a6989586621679184997 :: Ordering) Source # | |
Defined in Data.Ord.Singletons |
type family ThenCmpSym2 (a6989586621679184996 :: Ordering) (a6989586621679184997 :: Ordering) :: Ordering where ... Source #
ThenCmpSym2 a6989586621679184996 a6989586621679184997 = ThenCmp a6989586621679184996 a6989586621679184997 |
data CompareSym0 :: (~>) a ((~>) a Ordering) Source #
Instances
SOrd a => SingI (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # | |
Defined in Data.Ord.Singletons sing :: Sing CompareSym0 | |
SuppressUnusedWarnings (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679185012 :: a) Source # | |
Defined in Data.Ord.Singletons type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679185012 :: a) = CompareSym1 a6989586621679185012 |
data CompareSym1 (a6989586621679185012 :: a) :: (~>) a Ordering Source #
Instances
SOrd a => SingI1 (CompareSym1 :: a -> TyFun a Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons liftSing :: forall (x :: k1). Sing x -> Sing (CompareSym1 x) | |
(SOrd a, SingI d) => SingI (CompareSym1 d :: TyFun a Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons sing :: Sing (CompareSym1 d) | |
SuppressUnusedWarnings (CompareSym1 a6989586621679185012 :: TyFun a Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (CompareSym1 a6989586621679185012 :: TyFun a Ordering -> Type) (a6989586621679185013 :: a) Source # | |
Defined in Data.Ord.Singletons type Apply (CompareSym1 a6989586621679185012 :: TyFun a Ordering -> Type) (a6989586621679185013 :: a) = Compare a6989586621679185012 a6989586621679185013 |
type family CompareSym2 (a6989586621679185012 :: a) (a6989586621679185013 :: a) :: Ordering where ... Source #
CompareSym2 a6989586621679185012 a6989586621679185013 = Compare a6989586621679185012 a6989586621679185013 |
data (<@#@$) :: (~>) a ((~>) a Bool) infix 4 Source #
Instances
SOrd a => SingI ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679185017 :: a) Source # | |
Defined in Data.Ord.Singletons |
data (<@#@$$) (a6989586621679185017 :: a) :: (~>) a Bool infix 4 Source #
Instances
SOrd a => SingI1 ((<@#@$$) :: a -> TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
(SOrd a, SingI d) => SingI ((<@#@$$) d :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((<@#@$$) a6989586621679185017 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((<@#@$$) a6989586621679185017 :: TyFun a Bool -> Type) (a6989586621679185018 :: a) Source # | |
Defined in Data.Ord.Singletons |
type family (a6989586621679185017 :: a) <@#@$$$ (a6989586621679185018 :: a) :: Bool where ... infix 4 Source #
data (<=@#@$) :: (~>) a ((~>) a Bool) infix 4 Source #
Instances
SOrd a => SingI ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679185022 :: a) Source # | |
Defined in Data.Ord.Singletons |
data (<=@#@$$) (a6989586621679185022 :: a) :: (~>) a Bool infix 4 Source #
Instances
SOrd a => SingI1 ((<=@#@$$) :: a -> TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
(SOrd a, SingI d) => SingI ((<=@#@$$) d :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((<=@#@$$) a6989586621679185022 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((<=@#@$$) a6989586621679185022 :: TyFun a Bool -> Type) (a6989586621679185023 :: a) Source # | |
Defined in Data.Ord.Singletons |
type family (a6989586621679185022 :: a) <=@#@$$$ (a6989586621679185023 :: a) :: Bool where ... infix 4 Source #
data (>@#@$) :: (~>) a ((~>) a Bool) infix 4 Source #
Instances
SOrd a => SingI ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679185027 :: a) Source # | |
Defined in Data.Ord.Singletons |
data (>@#@$$) (a6989586621679185027 :: a) :: (~>) a Bool infix 4 Source #
Instances
SOrd a => SingI1 ((>@#@$$) :: a -> TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
(SOrd a, SingI d) => SingI ((>@#@$$) d :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((>@#@$$) a6989586621679185027 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((>@#@$$) a6989586621679185027 :: TyFun a Bool -> Type) (a6989586621679185028 :: a) Source # | |
Defined in Data.Ord.Singletons |
type family (a6989586621679185027 :: a) >@#@$$$ (a6989586621679185028 :: a) :: Bool where ... infix 4 Source #
data (>=@#@$) :: (~>) a ((~>) a Bool) infix 4 Source #
Instances
SOrd a => SingI ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679185032 :: a) Source # | |
Defined in Data.Ord.Singletons |
data (>=@#@$$) (a6989586621679185032 :: a) :: (~>) a Bool infix 4 Source #
Instances
SOrd a => SingI1 ((>=@#@$$) :: a -> TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
(SOrd a, SingI d) => SingI ((>=@#@$$) d :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings ((>=@#@$$) a6989586621679185032 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply ((>=@#@$$) a6989586621679185032 :: TyFun a Bool -> Type) (a6989586621679185033 :: a) Source # | |
Defined in Data.Ord.Singletons |
type family (a6989586621679185032 :: a) >=@#@$$$ (a6989586621679185033 :: a) :: Bool where ... infix 4 Source #
data MaxSym0 :: (~>) a ((~>) a a) Source #
Instances
SOrd a => SingI (MaxSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings (MaxSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679185037 :: a) Source # | |
Defined in Data.Ord.Singletons |
data MaxSym1 (a6989586621679185037 :: a) :: (~>) a a Source #
Instances
SOrd a => SingI1 (MaxSym1 :: a -> TyFun a a -> Type) Source # | |
Defined in Data.Ord.Singletons | |
(SOrd a, SingI d) => SingI (MaxSym1 d :: TyFun a a -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings (MaxSym1 a6989586621679185037 :: TyFun a a -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (MaxSym1 a6989586621679185037 :: TyFun a a -> Type) (a6989586621679185038 :: a) Source # | |
Defined in Data.Ord.Singletons |
data MinSym0 :: (~>) a ((~>) a a) Source #
Instances
SOrd a => SingI (MinSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings (MinSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679185042 :: a) Source # | |
Defined in Data.Ord.Singletons |
data MinSym1 (a6989586621679185042 :: a) :: (~>) a a Source #
Instances
SOrd a => SingI1 (MinSym1 :: a -> TyFun a a -> Type) Source # | |
Defined in Data.Ord.Singletons | |
(SOrd a, SingI d) => SingI (MinSym1 d :: TyFun a a -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings (MinSym1 a6989586621679185042 :: TyFun a a -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (MinSym1 a6989586621679185042 :: TyFun a a -> Type) (a6989586621679185043 :: a) Source # | |
Defined in Data.Ord.Singletons |
data ComparingSym0 :: (~>) ((~>) b a) ((~>) b ((~>) b Ordering)) Source #
Instances
SOrd a => SingI (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679185003 :: b ~> a) Source # | |
Defined in Data.Ord.Singletons type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679185003 :: b ~> a) = ComparingSym1 a6989586621679185003 |
data ComparingSym1 (a6989586621679185003 :: (~>) b a) :: (~>) b ((~>) b Ordering) Source #
Instances
SOrd a => SingI1 (ComparingSym1 :: (b ~> a) -> TyFun b (b ~> Ordering) -> Type) Source # | |
Defined in Data.Ord.Singletons liftSing :: forall (x :: k1). Sing x -> Sing (ComparingSym1 x) | |
(SOrd a, SingI d) => SingI (ComparingSym1 d :: TyFun b (b ~> Ordering) -> Type) Source # | |
Defined in Data.Ord.Singletons sing :: Sing (ComparingSym1 d) | |
SuppressUnusedWarnings (ComparingSym1 a6989586621679185003 :: TyFun b (b ~> Ordering) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (ComparingSym1 a6989586621679185003 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679185004 :: b) Source # | |
Defined in Data.Ord.Singletons type Apply (ComparingSym1 a6989586621679185003 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679185004 :: b) = ComparingSym2 a6989586621679185003 a6989586621679185004 |
data ComparingSym2 (a6989586621679185003 :: (~>) b a) (a6989586621679185004 :: b) :: (~>) b Ordering Source #
Instances
(SOrd a, SingI d) => SingI1 (ComparingSym2 d :: b -> TyFun b Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons liftSing :: forall (x :: k1). Sing x -> Sing (ComparingSym2 d x) | |
SOrd a => SingI2 (ComparingSym2 :: (b ~> a) -> b -> TyFun b Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ComparingSym2 x y) | |
(SOrd a, SingI d1, SingI d2) => SingI (ComparingSym2 d1 d2 :: TyFun b Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons sing :: Sing (ComparingSym2 d1 d2) | |
SuppressUnusedWarnings (ComparingSym2 a6989586621679185003 a6989586621679185004 :: TyFun b Ordering -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (ComparingSym2 a6989586621679185003 a6989586621679185004 :: TyFun b Ordering -> Type) (a6989586621679185005 :: b) Source # | |
Defined in Data.Ord.Singletons type Apply (ComparingSym2 a6989586621679185003 a6989586621679185004 :: TyFun b Ordering -> Type) (a6989586621679185005 :: b) = Comparing a6989586621679185003 a6989586621679185004 a6989586621679185005 |
type family ComparingSym3 (a6989586621679185003 :: (~>) b a) (a6989586621679185004 :: b) (a6989586621679185005 :: b) :: Ordering where ... Source #
ComparingSym3 a6989586621679185003 a6989586621679185004 a6989586621679185005 = Comparing a6989586621679185003 a6989586621679185004 a6989586621679185005 |
data DownSym0 :: (~>) a (Down (a :: Type)) Source #
Instances
SingI (DownSym0 :: TyFun a (Down a) -> Type) Source # | |
Defined in Data.Ord.Singletons | |
SuppressUnusedWarnings (DownSym0 :: TyFun a (Down a) -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (DownSym0 :: TyFun a (Down a) -> Type) (a6989586621679195717 :: a) Source # | |
Defined in Data.Ord.Singletons |
data GetDownSym0 :: (~>) (Down (a :: Type)) a Source #
Instances
SingI (GetDownSym0 :: TyFun (Down a) a -> Type) Source # | |
Defined in Data.Ord.Singletons sing :: Sing GetDownSym0 | |
SuppressUnusedWarnings (GetDownSym0 :: TyFun (Down a) a -> Type) Source # | |
Defined in Data.Ord.Singletons suppressUnusedWarnings :: () # | |
type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679195720 :: Down a) Source # | |
Defined in Data.Ord.Singletons type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679195720 :: Down a) = GetDown a6989586621679195720 |
type family GetDownSym1 (a6989586621679195720 :: Down (a :: Type)) :: a where ... Source #
GetDownSym1 a6989586621679195720 = GetDown a6989586621679195720 |