| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Nat
Synopsis
- data Nat
- type family NatPlus a a where ...
- type family NatMul a a where ...
- type family NatMinus a a where ...
- type family NatAbs a where ...
- type family NatSignum a where ...
- natPlus :: Nat -> Nat -> Nat
- natMul :: Nat -> Nat -> Nat
- natMinus :: Nat -> Nat -> Nat
- natAbs :: Nat -> Nat
- natSignum :: Nat -> Nat
- someNatVal :: Integer -> Maybe (SomeSing Nat)
- data SNat :: Nat -> Type where
- type family Sing :: k -> Type
- class PNum a
- class SNum a
- data SSym0 a6989586621679056679 where
- type SSym1 (a6989586621679056679 :: Nat) = S a6989586621679056679 :: Nat
- type ZSym0 = Z :: Nat
- type family Lit n where ...
- data LitSym0 a6989586621679102719 where
- type LitSym1 (a6989586621679102719 :: Nat) = Lit a6989586621679102719 :: Nat
- type SLit n = Sing (Lit n)
- sLit :: forall (n :: Nat). SingI (Lit n) => Sing (Lit n)
Documentation
Instances
| Eq Nat Source # | |
| Num Nat Source # | |
| Ord Nat Source # | |
| Show Nat Source # | |
| PShow Nat Source # | |
| SShow Nat => SShow Nat Source # | |
Defined in Data.Nat Methods sShowsPrec :: forall (t1 :: Nat0) (t2 :: Nat) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) # sShow_ :: forall (t :: Nat). Sing t -> Sing (Apply Show_Sym0 t) # sShowList :: forall (t1 :: [Nat]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) # | |
| PNum Nat Source # | |
| SNum Nat Source # | |
Defined in Data.Nat Methods (%+) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) # (%-) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (-@#@$) t1) t2) # (%*) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) # sNegate :: forall (t :: Nat). Sing t -> Sing (Apply NegateSym0 t) # sAbs :: forall (t :: Nat). Sing t -> Sing (Apply AbsSym0 t) # sSignum :: forall (t :: Nat). Sing t -> Sing (Apply SignumSym0 t) # sFromInteger :: forall (t :: Nat0). Sing t -> Sing (Apply FromIntegerSym0 t) # | |
| POrd Nat Source # | |
| SOrd Nat => SOrd Nat Source # | |
Defined in Data.Nat Methods sCompare :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) # (%<) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) # (%<=) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) # (%>) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) # (%>=) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) # sMax :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) # sMin :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) # | |
| SEq Nat => SEq Nat Source # | |
| PEq Nat Source # | |
| SDecide Nat => SDecide Nat Source # | |
| SingKind Nat Source # | |
| SDecide Nat => TestCoercion SNat Source # | |
| SDecide Nat => TestEquality SNat Source # | |
| SingI 'Z Source # | |
| SingI n => SingI ('S n :: Nat) Source # | |
| SuppressUnusedWarnings LitSym0 Source # | |
Defined in Data.Nat Methods suppressUnusedWarnings :: () # | |
| SuppressUnusedWarnings SSym0 Source # | |
Defined in Data.Nat Methods suppressUnusedWarnings :: () # | |
| SingI SSym0 Source # | |
| type Sing Source # | |
| type Demote Nat Source # | |
| type Show_ (arg :: Nat) Source # | |
| type FromInteger a Source # | |
Defined in Data.Nat type FromInteger a | |
| type Signum (a :: Nat) Source # | |
| type Abs (a :: Nat) Source # | |
| type Negate (arg :: Nat) Source # | |
| type ShowList (arg :: [Nat]) arg1 Source # | |
| type (a1 :: Nat) * (a2 :: Nat) Source # | |
| type (a1 :: Nat) - (a2 :: Nat) Source # | |
| type (a1 :: Nat) + (a2 :: Nat) Source # | |
| type Min (arg :: Nat) (arg1 :: Nat) Source # | |
| type Max (arg :: Nat) (arg1 :: Nat) Source # | |
| type (arg :: Nat) >= (arg1 :: Nat) Source # | |
| type (arg :: Nat) > (arg1 :: Nat) Source # | |
| type (arg :: Nat) <= (arg1 :: Nat) Source # | |
| type (arg :: Nat) < (arg1 :: Nat) Source # | |
| type Compare (a1 :: Nat) (a2 :: Nat) Source # | |
| type (x :: Nat) /= (y :: Nat) Source # | |
| type (a :: Nat) == (b :: Nat) Source # | |
| type ShowsPrec a1 (a2 :: Nat) a3 Source # | |
| type Apply LitSym0 (a6989586621679102719 :: Nat) Source # | |
| type Apply SSym0 (a6989586621679056679 :: Nat) Source # | |
type family Sing :: k -> Type #
The singleton kind-indexed type family.
Instances
Minimal complete definition
(%+), (%*), sAbs, sSignum, sFromInteger
Instances
| SNum Nat | |
Defined in Data.Singletons.Prelude.Num Methods (%+) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) # (%-) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (-@#@$) t1) t2) # (%*) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) # sNegate :: forall (t :: Nat). Sing t -> Sing (Apply NegateSym0 t) # sAbs :: forall (t :: Nat). Sing t -> Sing (Apply AbsSym0 t) # sSignum :: forall (t :: Nat). Sing t -> Sing (Apply SignumSym0 t) # sFromInteger :: forall (t :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t) # | |
| SNum Nat Source # | |
Defined in Data.Nat Methods (%+) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) # (%-) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (-@#@$) t1) t2) # (%*) :: forall (t1 :: Nat) (t2 :: Nat). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) # sNegate :: forall (t :: Nat). Sing t -> Sing (Apply NegateSym0 t) # sAbs :: forall (t :: Nat). Sing t -> Sing (Apply AbsSym0 t) # sSignum :: forall (t :: Nat). Sing t -> Sing (Apply SignumSym0 t) # sFromInteger :: forall (t :: Nat0). Sing t -> Sing (Apply FromIntegerSym0 t) # | |
| SNum a => SNum (Down a) | |
Defined in Data.Singletons.Prelude.Num Methods (%+) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) # (%-) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (-@#@$) t1) t2) # (%*) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) # sNegate :: forall (t :: Down a). Sing t -> Sing (Apply NegateSym0 t) # sAbs :: forall (t :: Down a). Sing t -> Sing (Apply AbsSym0 t) # sSignum :: forall (t :: Down a). Sing t -> Sing (Apply SignumSym0 t) # sFromInteger :: forall (t :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t) # | |
data SSym0 a6989586621679056679 where Source #
Constructors
| SSym0KindInference :: SameKind (Apply SSym0 arg) (SSym1 arg) => SSym0 a6989586621679056679 |
type family Lit n where ... Source #
Provides a shorthand for Nat-s using GHC.TypeLits, for example:
>>>:kind! Lit 3Lit 3 :: Nat = 'S ('S ('S 'Z))