Copyright | (C) 2014 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (eir@cis.upenn.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines and exports singletons useful for the Nat and Symbol kinds. This exports the internal, unsafe constructors. Use Data.Singletons.TypeLits for a safe interface.
- data Nat :: *
- data Symbol :: *
- data family Sing (a :: k)
- type SNat x = Sing x
- type SSymbol x = Sing x
- withKnownNat :: Sing n -> (KnownNat n => r) -> r
- withKnownSymbol :: Sing n -> (KnownSymbol n => r) -> r
- type family Error (str :: k0) :: k
- data ErrorSym0 l
- type ErrorSym1 t = Error t
- sError :: Sing (str :: Symbol) -> a
- class KnownNat n
- natVal :: KnownNat n => proxy n -> Integer
- class KnownSymbol n
- symbolVal :: KnownSymbol n => proxy n -> String
- type (:^) a b = a ^ b
- data (:^$) l
- data l :^$$ l
- type (:^$$$) t t = (:^) t t
Documentation
(Kind) This is the kind of type-level natural numbers.
SNum Nat Source # | |
SEnum Nat Source # | |
PNum Nat (Proxy * Nat) Source # | |
PEnum Nat (Proxy * Nat) Source # | |
SuppressUnusedWarnings (Nat -> TyFun Nat Nat -> *) (:^$$) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun Nat Nat -> *) -> *) (:^$) Source # | |
SuppressUnusedWarnings ((TyFun a1627953316 Bool -> Type) -> TyFun [a1627953316] (Maybe Nat) -> *) (FindIndexSym1 a1627953316) Source # | |
SuppressUnusedWarnings ((TyFun a1627953315 Bool -> Type) -> TyFun [a1627953315] [Nat] -> *) (FindIndicesSym1 a1627953315) Source # | |
SuppressUnusedWarnings ([a1627953289] -> TyFun Nat a1627953289 -> *) ((:!!$$) a1627953289) Source # | |
SuppressUnusedWarnings (Nat -> TyFun [a1627953305] ([a1627953305], [a1627953305]) -> *) (SplitAtSym1 a1627953305) Source # | |
SuppressUnusedWarnings (Nat -> TyFun [a1627953307] [a1627953307] -> *) (TakeSym1 a1627953307) Source # | |
SuppressUnusedWarnings (Nat -> TyFun [a1627953306] [a1627953306] -> *) (DropSym1 a1627953306) Source # | |
SuppressUnusedWarnings (Nat -> TyFun a1627953291 [a1627953291] -> *) (ReplicateSym1 a1627953291) Source # | |
SuppressUnusedWarnings (a1627953318 -> TyFun [a1627953318] (Maybe Nat) -> *) (ElemIndexSym1 a1627953318) Source # | |
SuppressUnusedWarnings (a1627953317 -> TyFun [a1627953317] [Nat] -> *) (ElemIndicesSym1 a1627953317) Source # | |
SuppressUnusedWarnings (TyFun (TyFun a1627953316 Bool -> Type) (TyFun [a1627953316] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a1627953316) Source # | |
SuppressUnusedWarnings (TyFun (TyFun a1627953315 Bool -> Type) (TyFun [a1627953315] [Nat] -> Type) -> *) (FindIndicesSym0 a1627953315) Source # | |
SuppressUnusedWarnings (TyFun [a1627953292] Nat -> *) (LengthSym0 a1627953292) Source # | |
SuppressUnusedWarnings (TyFun [a1627953289] (TyFun Nat a1627953289 -> Type) -> *) ((:!!$) a1627953289) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun [a1627953305] ([a1627953305], [a1627953305]) -> Type) -> *) (SplitAtSym0 a1627953305) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun [a1627953307] [a1627953307] -> Type) -> *) (TakeSym0 a1627953307) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun [a1627953306] [a1627953306] -> Type) -> *) (DropSym0 a1627953306) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun a1627953291 [a1627953291] -> Type) -> *) (ReplicateSym0 a1627953291) Source # | |
SuppressUnusedWarnings (TyFun Nat a1627817219 -> *) (FromIntegerSym0 a1627817219) Source # | |
SuppressUnusedWarnings (TyFun Nat a1627864213 -> *) (ToEnumSym0 a1627864213) Source # | |
SuppressUnusedWarnings (TyFun a1627864213 Nat -> *) (FromEnumSym0 a1627864213) Source # | |
SuppressUnusedWarnings (TyFun a1627953318 (TyFun [a1627953318] (Maybe Nat) -> Type) -> *) (ElemIndexSym0 a1627953318) Source # | |
SuppressUnusedWarnings (TyFun a1627953317 (TyFun [a1627953317] [Nat] -> Type) -> *) (ElemIndicesSym0 a1627953317) Source # | |
type DemoteRep Nat Source # | |
data Sing Nat Source # | |
type Negate Nat a Source # | |
type Abs Nat a Source # | |
type Signum Nat a Source # | |
type FromInteger Nat a Source # | |
type Succ Nat a0 Source # | |
type Pred Nat a0 Source # | |
type ToEnum Nat a0 Source # | |
type FromEnum Nat a0 Source # | |
type (==) Nat a b | |
type (:==) Nat a b Source # | |
type (:/=) Nat x y Source # | |
type Compare Nat a b Source # | |
type (:<) Nat arg0 arg1 Source # | |
type (:<=) Nat arg0 arg1 Source # | |
type (:>) Nat arg0 arg1 Source # | |
type (:>=) Nat arg0 arg1 Source # | |
type Max Nat arg0 arg1 Source # | |
type Min Nat arg0 arg1 Source # | |
type (:+) Nat a b Source # | |
type (:-) Nat a b Source # | |
type (:*) Nat a b Source # | |
type EnumFromTo Nat a0 a1 Source # | |
type EnumFromThenTo Nat a0 a1 a2 Source # | |
type Apply Nat Nat ((:^$$) l1) l0 Source # | |
type Apply Nat k2 (FromIntegerSym0 k2) l0 Source # | |
type Apply Nat k2 (ToEnumSym0 k2) l0 Source # | |
type Apply a1627864213 Nat (FromEnumSym0 a1627864213) l0 Source # | |
type Apply Nat a1627953289 ((:!!$$) a1627953289 l1) l0 Source # | |
type Apply Nat (TyFun Nat Nat -> *) (:^$) l0 Source # | |
type Apply Nat (TyFun [a1627953305] ([a1627953305], [a1627953305]) -> Type) (SplitAtSym0 a1627953305) l0 Source # | |
type Apply Nat (TyFun [a1627953307] [a1627953307] -> Type) (TakeSym0 a1627953307) l0 Source # | |
type Apply Nat (TyFun [a1627953306] [a1627953306] -> Type) (DropSym0 a1627953306) l0 Source # | |
type Apply Nat (TyFun a1627953291 [a1627953291] -> Type) (ReplicateSym0 a1627953291) l0 Source # | |
type Apply a1627953318 (TyFun [a1627953318] (Maybe Nat) -> Type) (ElemIndexSym0 a1627953318) l0 Source # | |
type Apply a1627953317 (TyFun [a1627953317] [Nat] -> Type) (ElemIndicesSym0 a1627953317) l0 Source # | |
type Apply [a1627953292] Nat (LengthSym0 a1627953292) l0 Source # | |
type Apply [a1627953318] (Maybe Nat) (ElemIndexSym1 a1627953318 l1) l0 Source # | |
type Apply [a1627953316] (Maybe Nat) (FindIndexSym1 a1627953316 l1) l0 Source # | |
type Apply [a1627953317] [Nat] (ElemIndicesSym1 a1627953317 l1) l0 Source # | |
type Apply [a1627953315] [Nat] (FindIndicesSym1 a1627953315 l1) l0 Source # | |
type Apply [a1627953289] (TyFun Nat a1627953289 -> Type) ((:!!$) a1627953289) l0 Source # | |
type Apply (TyFun a1627953316 Bool -> Type) (TyFun [a1627953316] (Maybe Nat) -> Type) (FindIndexSym0 a1627953316) l0 Source # | |
type Apply (TyFun a1627953315 Bool -> Type) (TyFun [a1627953315] [Nat] -> Type) (FindIndicesSym0 a1627953315) l0 Source # | |
(Kind) This is the kind of type-level symbols. Declared here because class IP needs it
KnownSymbol a => SingI Symbol a | |
SingKind Symbol (KProxy Symbol) | |
data Sing Symbol | |
type DemoteRep Symbol Source # | |
data Sing Symbol Source # | |
type (==) Symbol a b | |
type (:==) Symbol a b Source # | |
type (:/=) Symbol x y Source # | |
type Compare Symbol a b Source # | |
type (:<) Symbol arg0 arg1 Source # | |
type (:<=) Symbol arg0 arg1 Source # | |
type (:>) Symbol arg0 arg1 Source # | |
type (:>=) Symbol arg0 arg1 Source # | |
type Max Symbol arg0 arg1 Source # | |
type Min Symbol arg0 arg1 Source # | |
type DemoteRep Symbol (KProxy Symbol) | |
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 # | |
withKnownNat :: Sing n -> (KnownNat n => r) -> r Source #
Given a singleton for Nat
, call something requiring a
KnownNat
instance.
withKnownSymbol :: Sing n -> (KnownSymbol n => r) -> r Source #
Given a singleton for Symbol
, call something requiring
a KnownSymbol
instance.
type family Error (str :: k0) :: k Source #
The promotion of error
. This version is more poly-kinded for
easier use.
This class gives the integer associated with a type-level natural. There are instances of the class for every concrete literal: 0, 1, 2, etc.
Since: 4.7.0.0
natSing
class KnownSymbol n #
This class gives the string associated with a type-level symbol. There are instances of the class for every concrete literal: "hello", etc.
Since: 4.7.0.0
symbolSing
symbolVal :: KnownSymbol n => proxy n -> String #
Since: 4.7.0.0