Copyright | (C) 2013 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (eir@cis.upenn.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- class (PEq (Proxy :: Proxy a), kproxy ~ Proxy) => POrd kproxy where
- class SEq a => SOrd a where
- thenCmp :: Ordering -> Ordering -> Ordering
- type family ThenCmp (a :: Ordering) (a :: Ordering) :: Ordering where ...
- sThenCmp :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ThenCmpSym0 t) t :: Ordering)
- data family Sing (a :: k)
- data ThenCmpSym0 l
- data ThenCmpSym1 l l
- type ThenCmpSym2 t t = ThenCmp t t
- type LTSym0 = LT
- type EQSym0 = EQ
- type GTSym0 = GT
- data CompareSym0 l
- data CompareSym1 l l
- type CompareSym2 t t = Compare t t
- data (:<$) l
- data l :<$$ l
- type (:<$$$) t t = (:<) t t
- data (:<=$) l
- data l :<=$$ l
- type (:<=$$$) t t = (:<=) t t
- data (:>$) l
- data l :>$$ l
- type (:>$$$) t t = (:>) t t
- data (:>=$) l
- data l :>=$$ l
- type (:>=$$$) t t = (:>=) t t
- data MaxSym0 l
- data MaxSym1 l l
- type MaxSym2 t t = Max t t
- data MinSym0 l
- data MinSym1 l l
- type MinSym2 t t = Min t t
Documentation
class (PEq (Proxy :: Proxy a), kproxy ~ Proxy) => POrd kproxy Source #
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 #
POrd Bool (Proxy * Bool) Source # | |
POrd Ordering (Proxy * Ordering) Source # | |
POrd () (Proxy * ()) Source # | |
POrd [a0] (Proxy * [a0]) Source # | |
POrd (Maybe a0) (Proxy * (Maybe a0)) Source # | |
POrd (NonEmpty a0) (Proxy * (NonEmpty a0)) Source # | |
POrd (Either a0 b0) (Proxy * (Either a0 b0)) Source # | |
POrd (a0, b0) (Proxy * (a0, b0)) Source # | |
POrd (a0, b0, c0) (Proxy * (a0, b0, c0)) Source # | |
POrd (a0, b0, c0, d0) (Proxy * (a0, b0, c0, d0)) Source # | |
POrd (a0, b0, c0, d0, e0) (Proxy * (a0, b0, c0, d0, e0)) Source # | |
POrd (a0, b0, c0, d0, e0, f0) (Proxy * (a0, b0, c0, d0, e0, f0)) Source # | |
POrd (a0, b0, c0, d0, e0, f0, g0) (Proxy * (a0, b0, c0, d0, e0, f0, g0)) Source # | |
class SEq a => SOrd a where Source #
sCompare :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering) Source #
(%:<) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:<$) t) t :: Bool) infix 4 Source #
(%:<=) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:<=$) t) t :: Bool) infix 4 Source #
(%:>) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:>$) t) t :: Bool) infix 4 Source #
(%:>=) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:>=$) t) t :: Bool) infix 4 Source #
sMax :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t :: a) Source #
sMin :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t :: a) Source #
sCompare :: forall t t. (Apply (Apply CompareSym0 t) t ~ Apply (Apply Compare_1627683010Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t :: Ordering) Source #
(%:<) :: forall t t. (Apply (Apply (:<$) t) t ~ Apply (Apply TFHelper_1627683043Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:<$) t) t :: Bool) infix 4 Source #
(%:<=) :: forall t t. (Apply (Apply (:<=$) t) t ~ Apply (Apply TFHelper_1627683076Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:<=$) t) t :: Bool) infix 4 Source #
(%:>) :: forall t t. (Apply (Apply (:>$) t) t ~ Apply (Apply TFHelper_1627683109Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:>$) t) t :: Bool) infix 4 Source #
(%:>=) :: forall t t. (Apply (Apply (:>=$) t) t ~ Apply (Apply TFHelper_1627683142Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply (:>=$) t) t :: Bool) infix 4 Source #
sMax :: forall t t. (Apply (Apply MaxSym0 t) t ~ Apply (Apply Max_1627683175Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t :: a) Source #
sMin :: forall t t. (Apply (Apply MinSym0 t) t ~ Apply (Apply Min_1627683208Sym0 t) t) => Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t :: a) Source #
SOrd Bool Source # | |
SOrd Ordering Source # | |
SOrd () Source # | |
(SOrd a0, SOrd [a0]) => SOrd [a0] Source # | |
SOrd a0 => SOrd (Maybe a0) Source # | |
(SOrd a0, SOrd [a0]) => SOrd (NonEmpty a0) Source # | |
(SOrd a0, SOrd b0) => SOrd (Either a0 b0) Source # | |
(SOrd a0, SOrd b0) => SOrd (a0, b0) Source # | |
(SOrd a0, SOrd b0, SOrd c0) => SOrd (a0, b0, c0) Source # | |
(SOrd a0, SOrd b0, SOrd c0, SOrd d0) => SOrd (a0, b0, c0, d0) Source # | |
(SOrd a0, SOrd b0, SOrd c0, SOrd d0, SOrd e0) => SOrd (a0, b0, c0, d0, e0) Source # | |
(SOrd a0, SOrd b0, SOrd c0, SOrd d0, SOrd e0, SOrd f0) => SOrd (a0, b0, c0, d0, e0, f0) Source # | |
(SOrd a0, SOrd b0, SOrd c0, SOrd d0, SOrd e0, SOrd f0, SOrd g0) => SOrd (a0, b0, c0, d0, e0, f0, g0) Source # | |
sThenCmp :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ThenCmpSym0 t) t :: Ordering) Source #
data family Sing (a :: k) Source #
The singleton kind-indexed data family.
data Sing Bool Source # | |
data Sing Ordering Source # | |
data Sing * Source # | |
data Sing Nat Source # | |
data Sing Symbol Source # | |
data Sing () Source # | |
data Sing [a0] Source # | |
data Sing (Maybe a0) Source # | |
data Sing (NonEmpty a0) Source # | |
data Sing (Either a0 b0) Source # | |
data Sing (a0, b0) Source # | |
data Sing ((~>) k1 k2) Source # | |
data Sing (a0, b0, c0) Source # | |
data Sing (a0, b0, c0, d0) Source # | |
data Sing (a0, b0, c0, d0, e0) Source # | |
data Sing (a0, b0, c0, d0, e0, f0) Source # | |
data Sing (a0, b0, c0, d0, e0, f0, g0) Source # | |
Defunctionalization symbols
data ThenCmpSym0 l Source #
data ThenCmpSym1 l l Source #
SuppressUnusedWarnings (Ordering -> TyFun Ordering Ordering -> *) ThenCmpSym1 Source # | |
type Apply Ordering Ordering (ThenCmpSym1 l1) l0 Source # | |
type ThenCmpSym2 t t = ThenCmp t t Source #
data CompareSym0 l Source #
data CompareSym1 l l Source #
SuppressUnusedWarnings (a1627682221 -> TyFun a1627682221 Ordering -> *) (CompareSym1 a1627682221) Source # | |
type Apply a1627682221 Ordering (CompareSym1 a1627682221 l1) l0 Source # | |
type CompareSym2 t t = Compare t t Source #