Copyright | (C) 2013 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
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 a a 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 a where ...
- sThenCmp :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply ThenCmpSym0 t) t :: Ordering)
- type family Sing
- data SOrdering z where
- data SDown z where
- type family GetDown a where ...
- sGetDown :: forall (a :: Type) (t :: Down (a :: Type)). Sing t -> Sing (Apply GetDownSym0 t :: a)
- data ThenCmpSym0 a6989586621679394586
- data ThenCmpSym1 a6989586621679394586 a6989586621679394587
- type ThenCmpSym2 (a6989586621679394586 :: Ordering) (a6989586621679394587 :: Ordering) = ThenCmp a6989586621679394586 a6989586621679394587 :: Ordering
- type LTSym0 = 'LT :: Ordering
- type EQSym0 = 'EQ :: Ordering
- type GTSym0 = 'GT :: Ordering
- data CompareSym0 a6989586621679383640
- data CompareSym1 a6989586621679383640 a6989586621679383641
- type CompareSym2 (a6989586621679383640 :: a) (a6989586621679383641 :: a) = Compare a6989586621679383640 a6989586621679383641 :: Ordering
- data (<@#@$) a6989586621679383645
- data a6989586621679383645 <@#@$$ a6989586621679383646
- type (<@#@$$$) (a6989586621679383645 :: a) (a6989586621679383646 :: a) = (<) a6989586621679383645 a6989586621679383646 :: Bool
- data (<=@#@$) a6989586621679383650
- data a6989586621679383650 <=@#@$$ a6989586621679383651
- type (<=@#@$$$) (a6989586621679383650 :: a) (a6989586621679383651 :: a) = (<=) a6989586621679383650 a6989586621679383651 :: Bool
- data (>@#@$) a6989586621679383655
- data a6989586621679383655 >@#@$$ a6989586621679383656
- type (>@#@$$$) (a6989586621679383655 :: a) (a6989586621679383656 :: a) = (>) a6989586621679383655 a6989586621679383656 :: Bool
- data (>=@#@$) a6989586621679383660
- data a6989586621679383660 >=@#@$$ a6989586621679383661
- type (>=@#@$$$) (a6989586621679383660 :: a) (a6989586621679383661 :: a) = (>=) a6989586621679383660 a6989586621679383661 :: Bool
- data MaxSym0 a6989586621679383665
- data MaxSym1 a6989586621679383665 a6989586621679383666
- type MaxSym2 (a6989586621679383665 :: a) (a6989586621679383666 :: a) = Max a6989586621679383665 a6989586621679383666 :: a
- data MinSym0 a6989586621679383670
- data MinSym1 a6989586621679383670 a6989586621679383671
- type MinSym2 (a6989586621679383670 :: a) (a6989586621679383671 :: a) = Min a6989586621679383670 a6989586621679383671 :: a
- data ComparingSym0 a6989586621679383631
- data ComparingSym1 a6989586621679383631 a6989586621679383632
- data ComparingSym2 a6989586621679383631 a6989586621679383632 a6989586621679383633
- type ComparingSym3 (a6989586621679383631 :: (~>) b a) (a6989586621679383632 :: b) (a6989586621679383633 :: b) = Comparing a6989586621679383631 a6989586621679383632 a6989586621679383633 :: Ordering
- data DownSym0 a6989586621679393010
- type DownSym1 (a6989586621679393010 :: a) = 'Down a6989586621679393010 :: Down (a :: Type)
- data GetDownSym0 a6989586621679393013
- type GetDownSym1 (a6989586621679393013 :: Down (a :: Type)) = GetDown a6989586621679393013 :: a
Documentation
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 #
Instances
POrd Bool Source # | |
POrd Ordering Source # | |
POrd Nat Source # | |
POrd Symbol Source # | |
POrd () Source # | |
POrd Void Source # | |
POrd All Source # | |
POrd Any Source # | |
POrd [a] Source # | |
POrd (Maybe a) Source # | |
POrd (Min a) Source # | |
POrd (Max a) Source # | |
POrd (First a) Source # | |
POrd (Last a) Source # | |
POrd (WrappedMonoid m) Source # | |
POrd (Option a) Source # | |
POrd (Identity a) Source # | |
POrd (First a) Source # | |
POrd (Last a) Source # | |
POrd (Dual a) Source # | |
POrd (Sum a) Source # | |
POrd (Product a) Source # | |
POrd (Down a) Source # | |
POrd (NonEmpty a) Source # | |
POrd (Either a b) Source # | |
POrd (a, b) Source # | |
POrd (Arg a b) Source # | |
POrd (Proxy s) Source # | |
POrd (a, b, c) Source # | |
POrd (Const a b) 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_6989586621679383674Sym0 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_6989586621679383695Sym0 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_6989586621679383711Sym0 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_6989586621679383727Sym0 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_6989586621679383743Sym0 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_6989586621679383759Sym0 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 Source # | |
Defined in Data.Singletons.Prelude.Ord 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 Ordering Source # | |
Defined in Data.Singletons.Prelude.Ord 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 Nat Source # | |
Defined in Data.Singletons.TypeLits.Internal sCompare :: forall (t :: Nat) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Nat) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Nat) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Nat) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Nat) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Nat) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Nat) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd Symbol Source # | |
Defined in Data.Singletons.TypeLits.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 () Source # | |
Defined in Data.Singletons.Prelude.Ord 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 Void Source # | |
Defined in Data.Singletons.Prelude.Ord 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 Bool => SOrd All Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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.Singletons.Prelude.Semigroup.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 a, SOrd [a]) => SOrd [a] Source # | |
Defined in Data.Singletons.Prelude.Ord 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 (Maybe a) Source # | |
Defined in Data.Singletons.Prelude.Ord 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 (Min a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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 a => SOrd (Max a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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 (First a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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.Singletons.Prelude.Semigroup.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 m => SOrd (WrappedMonoid m) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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 (Maybe a) => SOrd (Option a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.Internal sCompare :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
SOrd a => SOrd (Identity a) Source # | |
Defined in Data.Singletons.Prelude.Ord 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.Singletons.Prelude.Monoid 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.Singletons.Prelude.Monoid 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 (Dual a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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 (Sum a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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 (Product a) Source # | |
Defined in Data.Singletons.Prelude.Semigroup.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 (Down a) Source # | |
Defined in Data.Singletons.Prelude.Ord 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 [a]) => SOrd (NonEmpty a) Source # | |
Defined in Data.Singletons.Prelude.Ord 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 b) => SOrd (Either a b) Source # | |
Defined in Data.Singletons.Prelude.Ord 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 a, SOrd b) => SOrd (a, b) Source # | |
Defined in Data.Singletons.Prelude.Ord 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 (Arg a b) Source # | |
Defined in Data.Singletons.Prelude.Semigroup 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 (Proxy s) Source # | |
Defined in Data.Singletons.Prelude.Proxy 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 b, SOrd c) => SOrd (a, b, c) Source # | |
Defined in Data.Singletons.Prelude.Ord 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 (Const a b) Source # | |
Defined in Data.Singletons.Prelude.Const 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 d) => SOrd (a, b, c, d) Source # | |
Defined in Data.Singletons.Prelude.Ord 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.Singletons.Prelude.Ord 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.Singletons.Prelude.Ord 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.Singletons.Prelude.Ord 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 # |
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 #
The singleton kind-indexed type family.
Instances
data SOrdering z where Source #
SLT :: SOrdering ('LT :: Ordering) | |
SEQ :: SOrdering ('EQ :: Ordering) | |
SGT :: SOrdering ('GT :: Ordering) |
Instances
TestCoercion SOrdering Source # | |
Defined in Data.Singletons.Prelude.Instances | |
TestEquality SOrdering Source # | |
Defined in Data.Singletons.Prelude.Instances | |
Show (SOrdering z) Source # | |
Instances
SDecide a => TestCoercion (SDown :: Down a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord | |
SDecide a => TestEquality (SDown :: Down a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord |
sGetDown :: forall (a :: Type) (t :: Down (a :: Type)). Sing t -> Sing (Apply GetDownSym0 t :: a) Source #
Defunctionalization symbols
data ThenCmpSym0 a6989586621679394586 Source #
Instances
SingI ThenCmpSym0 Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing ThenCmpSym0 Source # | |
SuppressUnusedWarnings ThenCmpSym0 Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ThenCmpSym0 (a6989586621679394586 :: Ordering) Source # | |
Defined in Data.Singletons.Prelude.Ord |
data ThenCmpSym1 a6989586621679394586 a6989586621679394587 Source #
Instances
SingI d => SingI (ThenCmpSym1 d :: TyFun Ordering Ordering -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing (ThenCmpSym1 d) Source # | |
SuppressUnusedWarnings (ThenCmpSym1 a6989586621679394586 :: TyFun Ordering Ordering -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (ThenCmpSym1 a6989586621679394586 :: TyFun Ordering Ordering -> Type) (a6989586621679394587 :: Ordering) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ThenCmpSym1 a6989586621679394586 :: TyFun Ordering Ordering -> Type) (a6989586621679394587 :: Ordering) = ThenCmpSym2 a6989586621679394586 a6989586621679394587 |
type ThenCmpSym2 (a6989586621679394586 :: Ordering) (a6989586621679394587 :: Ordering) = ThenCmp a6989586621679394586 a6989586621679394587 :: Ordering Source #
data CompareSym0 a6989586621679383640 Source #
Instances
SOrd a => SingI (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing CompareSym0 Source # | |
SuppressUnusedWarnings (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679383640 :: a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679383640 :: a) = CompareSym1 a6989586621679383640 |
data CompareSym1 a6989586621679383640 a6989586621679383641 Source #
Instances
(SOrd a, SingI d) => SingI (CompareSym1 d :: TyFun a Ordering -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing (CompareSym1 d) Source # | |
SuppressUnusedWarnings (CompareSym1 a6989586621679383640 :: TyFun a Ordering -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (CompareSym1 a6989586621679383640 :: TyFun a Ordering -> Type) (a6989586621679383641 :: a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (CompareSym1 a6989586621679383640 :: TyFun a Ordering -> Type) (a6989586621679383641 :: a) = CompareSym2 a6989586621679383640 a6989586621679383641 |
type CompareSym2 (a6989586621679383640 :: a) (a6989586621679383641 :: a) = Compare a6989586621679383640 a6989586621679383641 :: Ordering Source #
data (<@#@$) a6989586621679383645 infix 4 Source #
Instances
SOrd a => SingI ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383645 :: a) Source # | |
data a6989586621679383645 <@#@$$ a6989586621679383646 infix 4 Source #
Instances
(SOrd a, SingI d) => SingI ((<@#@$$) d :: TyFun a Bool -> Type) Source # | |
SuppressUnusedWarnings ((<@#@$$) a6989586621679383645 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((<@#@$$) a6989586621679383645 :: TyFun a Bool -> Type) (a6989586621679383646 :: a) Source # | |
type (<@#@$$$) (a6989586621679383645 :: a) (a6989586621679383646 :: a) = (<) a6989586621679383645 a6989586621679383646 :: Bool infix 4 Source #
data (<=@#@$) a6989586621679383650 infix 4 Source #
Instances
SOrd a => SingI ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383650 :: a) Source # | |
data a6989586621679383650 <=@#@$$ a6989586621679383651 infix 4 Source #
Instances
(SOrd a, SingI d) => SingI ((<=@#@$$) d :: TyFun a Bool -> Type) Source # | |
SuppressUnusedWarnings ((<=@#@$$) a6989586621679383650 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((<=@#@$$) a6989586621679383650 :: TyFun a Bool -> Type) (a6989586621679383651 :: a) Source # | |
type (<=@#@$$$) (a6989586621679383650 :: a) (a6989586621679383651 :: a) = (<=) a6989586621679383650 a6989586621679383651 :: Bool infix 4 Source #
data (>@#@$) a6989586621679383655 infix 4 Source #
Instances
SOrd a => SingI ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383655 :: a) Source # | |
data a6989586621679383655 >@#@$$ a6989586621679383656 infix 4 Source #
Instances
(SOrd a, SingI d) => SingI ((>@#@$$) d :: TyFun a Bool -> Type) Source # | |
SuppressUnusedWarnings ((>@#@$$) a6989586621679383655 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((>@#@$$) a6989586621679383655 :: TyFun a Bool -> Type) (a6989586621679383656 :: a) Source # | |
type (>@#@$$$) (a6989586621679383655 :: a) (a6989586621679383656 :: a) = (>) a6989586621679383655 a6989586621679383656 :: Bool infix 4 Source #
data (>=@#@$) a6989586621679383660 infix 4 Source #
Instances
SOrd a => SingI ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
SuppressUnusedWarnings ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679383660 :: a) Source # | |
data a6989586621679383660 >=@#@$$ a6989586621679383661 infix 4 Source #
Instances
(SOrd a, SingI d) => SingI ((>=@#@$$) d :: TyFun a Bool -> Type) Source # | |
SuppressUnusedWarnings ((>=@#@$$) a6989586621679383660 :: TyFun a Bool -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply ((>=@#@$$) a6989586621679383660 :: TyFun a Bool -> Type) (a6989586621679383661 :: a) Source # | |
type (>=@#@$$$) (a6989586621679383660 :: a) (a6989586621679383661 :: a) = (>=) a6989586621679383660 a6989586621679383661 :: Bool infix 4 Source #
data MaxSym0 a6989586621679383665 Source #
Instances
data MaxSym1 a6989586621679383665 a6989586621679383666 Source #
Instances
(SOrd a, SingI d) => SingI (MaxSym1 d :: TyFun a a -> Type) Source # | |
SuppressUnusedWarnings (MaxSym1 a6989586621679383665 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (MaxSym1 a6989586621679383665 :: TyFun a a -> Type) (a6989586621679383666 :: a) Source # | |
type MaxSym2 (a6989586621679383665 :: a) (a6989586621679383666 :: a) = Max a6989586621679383665 a6989586621679383666 :: a Source #
data MinSym0 a6989586621679383670 Source #
Instances
data MinSym1 a6989586621679383670 a6989586621679383671 Source #
Instances
(SOrd a, SingI d) => SingI (MinSym1 d :: TyFun a a -> Type) Source # | |
SuppressUnusedWarnings (MinSym1 a6989586621679383670 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (MinSym1 a6989586621679383670 :: TyFun a a -> Type) (a6989586621679383671 :: a) Source # | |
type MinSym2 (a6989586621679383670 :: a) (a6989586621679383671 :: a) = Min a6989586621679383670 a6989586621679383671 :: a Source #
data ComparingSym0 a6989586621679383631 Source #
Instances
SOrd a => SingI (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing ComparingSym0 Source # | |
SuppressUnusedWarnings (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679383631 :: b ~> a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679383631 :: b ~> a) = ComparingSym1 a6989586621679383631 |
data ComparingSym1 a6989586621679383631 a6989586621679383632 Source #
Instances
(SOrd a, SingI d) => SingI (ComparingSym1 d :: TyFun b (b ~> Ordering) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing (ComparingSym1 d) Source # | |
SuppressUnusedWarnings (ComparingSym1 a6989586621679383631 :: TyFun b (b ~> Ordering) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (ComparingSym1 a6989586621679383631 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679383632 :: b) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym1 a6989586621679383631 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679383632 :: b) = ComparingSym2 a6989586621679383631 a6989586621679383632 |
data ComparingSym2 a6989586621679383631 a6989586621679383632 a6989586621679383633 Source #
Instances
(SOrd a, SingI d1, SingI d2) => SingI (ComparingSym2 d1 d2 :: TyFun b Ordering -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing (ComparingSym2 d1 d2) Source # | |
SuppressUnusedWarnings (ComparingSym2 a6989586621679383631 a6989586621679383632 :: TyFun b Ordering -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (ComparingSym2 a6989586621679383631 a6989586621679383632 :: TyFun b Ordering -> Type) (a6989586621679383633 :: b) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym2 a6989586621679383631 a6989586621679383632 :: TyFun b Ordering -> Type) (a6989586621679383633 :: b) = ComparingSym3 a6989586621679383631 a6989586621679383632 a6989586621679383633 |
type ComparingSym3 (a6989586621679383631 :: (~>) b a) (a6989586621679383632 :: b) (a6989586621679383633 :: b) = Comparing a6989586621679383631 a6989586621679383632 a6989586621679383633 :: Ordering Source #
data GetDownSym0 a6989586621679393013 Source #
Instances
SingI (GetDownSym0 :: TyFun (Down a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord sing :: Sing GetDownSym0 Source # | |
SuppressUnusedWarnings (GetDownSym0 :: TyFun (Down a) a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Ord suppressUnusedWarnings :: () Source # | |
type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679393013 :: Down a) Source # | |
Defined in Data.Singletons.Prelude.Ord type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679393013 :: Down a) = GetDownSym1 a6989586621679393013 |
type GetDownSym1 (a6989586621679393013 :: Down (a :: Type)) = GetDown a6989586621679393013 :: a Source #