Copyright | (C) 2014 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines and exports promoted and singleton versions of definitions from GHC.Num.
Be warned that some of the associated type families in the PNum
class
((+)
, (-)
, and (*)
) clash with their counterparts for Nat
in the
GHC.TypeLits module.
Synopsis
- class PNum a where
- class SNum a where
- (%+) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (+@#@$) t) t :: a)
- (%-) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (-@#@$) t) t :: a)
- (%*) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (*@#@$) t) t :: a)
- sNegate :: forall (t :: a). Sing t -> Sing (Apply NegateSym0 t :: a)
- sAbs :: forall (t :: a). Sing t -> Sing (Apply AbsSym0 t :: a)
- sSignum :: forall (t :: a). Sing t -> Sing (Apply SignumSym0 t :: a)
- sFromInteger :: forall (t :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t :: a)
- type family Subtract a a where ...
- sSubtract :: forall a (t :: a) (t :: a). SNum a => Sing t -> Sing t -> Sing (Apply (Apply SubtractSym0 t) t :: a)
- data (+@#@$) a6989586621679517796
- data a6989586621679517796 +@#@$$ a6989586621679517797
- type (+@#@$$$) (a6989586621679517796 :: a) (a6989586621679517797 :: a) = (+) a6989586621679517796 a6989586621679517797 :: a
- data (-@#@$) a6989586621679517801
- data a6989586621679517801 -@#@$$ a6989586621679517802
- type (-@#@$$$) (a6989586621679517801 :: a) (a6989586621679517802 :: a) = (-) a6989586621679517801 a6989586621679517802 :: a
- data (*@#@$) a6989586621679517806
- data a6989586621679517806 *@#@$$ a6989586621679517807
- type (*@#@$$$) (a6989586621679517806 :: a) (a6989586621679517807 :: a) = * a6989586621679517806 a6989586621679517807 :: a
- data NegateSym0 a6989586621679517810
- type NegateSym1 (a6989586621679517810 :: a) = Negate a6989586621679517810 :: a
- data AbsSym0 a6989586621679517813
- type AbsSym1 (a6989586621679517813 :: a) = Abs a6989586621679517813 :: a
- data SignumSym0 a6989586621679517816
- type SignumSym1 (a6989586621679517816 :: a) = Signum a6989586621679517816 :: a
- data FromIntegerSym0 a6989586621679517819
- type FromIntegerSym1 (a6989586621679517819 :: Nat) = FromInteger a6989586621679517819 :: a
- data SubtractSym0 a6989586621679517789
- data SubtractSym1 a6989586621679517789 a6989586621679517790
- type SubtractSym2 (a6989586621679517789 :: a) (a6989586621679517790 :: a) = Subtract a6989586621679517789 a6989586621679517790 :: a
Documentation
type (arg :: a) + (arg :: a) :: a infixl 6 Source #
type (arg :: a) - (arg :: a) :: a infixl 6 Source #
type (arg :: a) * (arg :: a) :: a infixl 7 Source #
type Negate (arg :: a) :: a Source #
type Abs (arg :: a) :: a Source #
type Signum (arg :: a) :: a Source #
type FromInteger (arg :: Nat) :: a Source #
(%+), (%*), sAbs, sSignum, sFromInteger
(%+) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (+@#@$) t) t :: a) infixl 6 Source #
(%-) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (-@#@$) t) t :: a) infixl 6 Source #
default (%-) :: forall (t :: a) (t :: a). (Apply (Apply (-@#@$) t) t :: a) ~ Apply (Apply TFHelper_6989586621679517822Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply (-@#@$) t) t :: a) Source #
(%*) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (*@#@$) t) t :: a) infixl 7 Source #
sNegate :: forall (t :: a). Sing t -> Sing (Apply NegateSym0 t :: a) Source #
default sNegate :: forall (t :: a). (Apply NegateSym0 t :: a) ~ Apply Negate_6989586621679517832Sym0 t => Sing t -> Sing (Apply NegateSym0 t :: a) Source #
sAbs :: forall (t :: a). Sing t -> Sing (Apply AbsSym0 t :: a) Source #
sSignum :: forall (t :: a). Sing t -> Sing (Apply SignumSym0 t :: a) Source #
sFromInteger :: forall (t :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t :: a) Source #
Instances
sSubtract :: forall a (t :: a) (t :: a). SNum a => Sing t -> Sing t -> Sing (Apply (Apply SubtractSym0 t) t :: a) Source #
Defunctionalization symbols
data (+@#@$) a6989586621679517796 infixl 6 Source #
Instances
data a6989586621679517796 +@#@$$ a6989586621679517797 infixl 6 Source #
Instances
(SNum a, SingI d) => SingI ((+@#@$$) d :: TyFun a a -> Type) Source # | |
SuppressUnusedWarnings ((+@#@$$) a6989586621679517796 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply ((+@#@$$) a6989586621679517796 :: TyFun a a -> Type) (a6989586621679517797 :: a) Source # | |
type (+@#@$$$) (a6989586621679517796 :: a) (a6989586621679517797 :: a) = (+) a6989586621679517796 a6989586621679517797 :: a infixl 6 Source #
data (-@#@$) a6989586621679517801 infixl 6 Source #
Instances
data a6989586621679517801 -@#@$$ a6989586621679517802 infixl 6 Source #
Instances
(SNum a, SingI d) => SingI ((-@#@$$) d :: TyFun a a -> Type) Source # | |
SuppressUnusedWarnings ((-@#@$$) a6989586621679517801 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply ((-@#@$$) a6989586621679517801 :: TyFun a a -> Type) (a6989586621679517802 :: a) Source # | |
type (-@#@$$$) (a6989586621679517801 :: a) (a6989586621679517802 :: a) = (-) a6989586621679517801 a6989586621679517802 :: a infixl 6 Source #
data (*@#@$) a6989586621679517806 infixl 7 Source #
Instances
data a6989586621679517806 *@#@$$ a6989586621679517807 infixl 7 Source #
Instances
(SNum a, SingI d) => SingI ((*@#@$$) d :: TyFun a a -> Type) Source # | |
SuppressUnusedWarnings ((*@#@$$) a6989586621679517806 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply ((*@#@$$) a6989586621679517806 :: TyFun a a -> Type) (a6989586621679517807 :: a) Source # | |
type (*@#@$$$) (a6989586621679517806 :: a) (a6989586621679517807 :: a) = * a6989586621679517806 a6989586621679517807 :: a infixl 7 Source #
data NegateSym0 a6989586621679517810 Source #
Instances
SNum a => SingI (NegateSym0 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num sing :: Sing NegateSym0 Source # | |
SuppressUnusedWarnings (NegateSym0 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679517810 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679517810 :: a) = NegateSym1 a6989586621679517810 |
type NegateSym1 (a6989586621679517810 :: a) = Negate a6989586621679517810 :: a Source #
data SignumSym0 a6989586621679517816 Source #
Instances
SNum a => SingI (SignumSym0 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num sing :: Sing SignumSym0 Source # | |
SuppressUnusedWarnings (SignumSym0 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679517816 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679517816 :: a) = SignumSym1 a6989586621679517816 |
type SignumSym1 (a6989586621679517816 :: a) = Signum a6989586621679517816 :: a Source #
data FromIntegerSym0 a6989586621679517819 Source #
Instances
SNum a => SingI (FromIntegerSym0 :: TyFun Nat a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num | |
SuppressUnusedWarnings (FromIntegerSym0 :: TyFun Nat a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply (FromIntegerSym0 :: TyFun Nat k2 -> Type) (a6989586621679517819 :: Nat) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (FromIntegerSym0 :: TyFun Nat k2 -> Type) (a6989586621679517819 :: Nat) = FromIntegerSym1 a6989586621679517819 :: k2 |
type FromIntegerSym1 (a6989586621679517819 :: Nat) = FromInteger a6989586621679517819 :: a Source #
data SubtractSym0 a6989586621679517789 Source #
Instances
SNum a => SingI (SubtractSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num sing :: Sing SubtractSym0 Source # | |
SuppressUnusedWarnings (SubtractSym0 :: TyFun a (a ~> a) -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679517789 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679517789 :: a) = SubtractSym1 a6989586621679517789 |
data SubtractSym1 a6989586621679517789 a6989586621679517790 Source #
Instances
(SNum a, SingI d) => SingI (SubtractSym1 d :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num sing :: Sing (SubtractSym1 d) Source # | |
SuppressUnusedWarnings (SubtractSym1 a6989586621679517789 :: TyFun a a -> Type) Source # | |
Defined in Data.Singletons.Prelude.Num suppressUnusedWarnings :: () Source # | |
type Apply (SubtractSym1 a6989586621679517789 :: TyFun a a -> Type) (a6989586621679517790 :: a) Source # | |
Defined in Data.Singletons.Prelude.Num type Apply (SubtractSym1 a6989586621679517789 :: TyFun a a -> Type) (a6989586621679517790 :: a) = SubtractSym2 a6989586621679517789 a6989586621679517790 |
type SubtractSym2 (a6989586621679517789 :: a) (a6989586621679517790 :: a) = Subtract a6989586621679517789 a6989586621679517790 :: a Source #