Copyright | (C) 2014 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines and exports singletons useful for the Nat and Symbol kinds.
- data Nat :: *
- data Symbol :: *
- data family Sing (a :: k)
- type SNat (x :: Nat) = Sing x
- type SSymbol (x :: Symbol) = 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 :: TyFun k06989586621679402464 k6989586621679402466)
- type ErrorSym1 (t :: k06989586621679402464) = Error t
- sError :: Sing (str :: Symbol) -> a
- class KnownNat (n :: Nat)
- data KnownNatSym0 (l :: TyFun Nat Constraint)
- type KnownNatSym1 (t :: Nat) = KnownNat t
- natVal :: KnownNat n => proxy n -> Integer
- class KnownSymbol (n :: Symbol)
- data KnownSymbolSym0 (l :: TyFun Symbol Constraint)
- type KnownSymbolSym1 (t :: Symbol) = KnownSymbol t
- symbolVal :: KnownSymbol n => proxy n -> String
- type (:^) a b = a ^ b
- data (:^$) l
- data (l :: Nat) :^$$ l
- type (:^$$$) (t :: Nat) (t :: Nat) = (:^) t t
Documentation
(Kind) This is the kind of type-level natural numbers.
SNum Nat Source # | |
PNum Nat Source # | |
SEnum Nat Source # | |
PEnum Nat Source # | |
SuppressUnusedWarnings (Nat -> TyFun Nat Nat -> *) (:^$$) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun Nat Nat -> *) -> *) (:^$) Source # | |
SuppressUnusedWarnings (TyFun Nat Constraint -> *) KnownNatSym0 Source # | |
SuppressUnusedWarnings ((TyFun a6989586621679458102 Bool -> Type) -> TyFun [a6989586621679458102] [Nat] -> *) (FindIndicesSym1 a6989586621679458102) Source # | |
SuppressUnusedWarnings ((TyFun a6989586621679458103 Bool -> Type) -> TyFun [a6989586621679458103] (Maybe Nat) -> *) (FindIndexSym1 a6989586621679458103) Source # | |
SuppressUnusedWarnings ([a6989586621679458076] -> TyFun Nat a6989586621679458076 -> *) ((:!!$$) a6989586621679458076) Source # | |
SuppressUnusedWarnings (Nat -> TyFun [a6989586621679458093] [a6989586621679458093] -> *) (DropSym1 a6989586621679458093) Source # | |
SuppressUnusedWarnings (Nat -> TyFun [a6989586621679458094] [a6989586621679458094] -> *) (TakeSym1 a6989586621679458094) Source # | |
SuppressUnusedWarnings (Nat -> TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> *) (SplitAtSym1 a6989586621679458092) Source # | |
SuppressUnusedWarnings (Nat -> TyFun a6989586621679458078 [a6989586621679458078] -> *) (ReplicateSym1 a6989586621679458078) Source # | |
SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> *) (TakeSym1 a6989586621679729633) Source # | |
SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> *) (DropSym1 a6989586621679729632) Source # | |
SuppressUnusedWarnings (Nat -> TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> *) (SplitAtSym1 a6989586621679729631) Source # | |
SuppressUnusedWarnings (a6989586621679458104 -> TyFun [a6989586621679458104] [Nat] -> *) (ElemIndicesSym1 a6989586621679458104) Source # | |
SuppressUnusedWarnings (a6989586621679458105 -> TyFun [a6989586621679458105] (Maybe Nat) -> *) (ElemIndexSym1 a6989586621679458105) Source # | |
SuppressUnusedWarnings (NonEmpty a6989586621679729611 -> TyFun Nat a6989586621679729611 -> *) ((:!!$$) a6989586621679729611) Source # | |
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type) -> *) (FindIndicesSym0 a6989586621679458102) Source # | |
SuppressUnusedWarnings (TyFun (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a6989586621679458103) Source # | |
SuppressUnusedWarnings (TyFun [a6989586621679458076] (TyFun Nat a6989586621679458076 -> Type) -> *) ((:!!$) a6989586621679458076) Source # | |
SuppressUnusedWarnings (TyFun [a6989586621679458079] Nat -> *) (LengthSym0 a6989586621679458079) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679458093] [a6989586621679458093] -> Type) -> *) (DropSym0 a6989586621679458093) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679458094] [a6989586621679458094] -> Type) -> *) (TakeSym0 a6989586621679458094) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> Type) -> *) (SplitAtSym0 a6989586621679458092) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun a6989586621679458078 [a6989586621679458078] -> Type) -> *) (ReplicateSym0 a6989586621679458078) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> Type) -> *) (TakeSym0 a6989586621679729633) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> Type) -> *) (DropSym0 a6989586621679729632) Source # | |
SuppressUnusedWarnings (TyFun Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type) -> *) (SplitAtSym0 a6989586621679729631) Source # | |
SuppressUnusedWarnings (TyFun Nat a6989586621679410509 -> *) (FromIntegerSym0 a6989586621679410509) Source # | |
SuppressUnusedWarnings (TyFun Nat a6989586621679809090 -> *) (ToEnumSym0 a6989586621679809090) Source # | |
SuppressUnusedWarnings (TyFun a6989586621679458104 (TyFun [a6989586621679458104] [Nat] -> Type) -> *) (ElemIndicesSym0 a6989586621679458104) Source # | |
SuppressUnusedWarnings (TyFun a6989586621679458105 (TyFun [a6989586621679458105] (Maybe Nat) -> Type) -> *) (ElemIndexSym0 a6989586621679458105) Source # | |
SuppressUnusedWarnings (TyFun a6989586621679809090 Nat -> *) (FromEnumSym0 a6989586621679809090) Source # | |
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type) -> *) ((:!!$) a6989586621679729611) Source # | |
SuppressUnusedWarnings (TyFun (NonEmpty a6989586621679729664) Nat -> *) (LengthSym0 a6989586621679729664) Source # | |
type Demote 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 a Source # | |
type Pred Nat a Source # | |
type ToEnum Nat a Source # | |
type FromEnum Nat a Source # | |
type (==) Nat a b | |
type (:==) Nat a b Source # | |
type (:/=) Nat x y Source # | |
type Compare Nat a b Source # | |
type (:<) Nat arg1 arg2 Source # | |
type (:<=) Nat arg1 arg2 Source # | |
type (:>) Nat arg1 arg2 Source # | |
type (:>=) Nat arg1 arg2 Source # | |
type Max Nat arg1 arg2 Source # | |
type Min Nat arg1 arg2 Source # | |
type (:+) Nat a b Source # | |
type (:-) Nat a b Source # | |
type (:*) Nat a b Source # | |
type EnumFromTo Nat a1 a2 Source # | |
type Apply Nat Constraint KnownNatSym0 l Source # | |
type EnumFromThenTo Nat a1 a2 a3 Source # | |
type Apply Nat Nat ((:^$$) l1) l2 Source # | |
type Apply Nat k2 (FromIntegerSym0 k2) l Source # | |
type Apply Nat k2 (ToEnumSym0 k2) l Source # | |
type Apply a Nat (FromEnumSym0 a) l Source # | |
type Apply Nat a ((:!!$$) a l1) l2 Source # | |
type Apply Nat a ((:!!$$) a l1) l2 Source # | |
type Apply Nat (TyFun Nat Nat -> *) (:^$) l Source # | |
type Apply Nat (TyFun [a6989586621679458093] [a6989586621679458093] -> Type) (DropSym0 a6989586621679458093) l Source # | |
type Apply Nat (TyFun [a6989586621679458094] [a6989586621679458094] -> Type) (TakeSym0 a6989586621679458094) l Source # | |
type Apply Nat (TyFun [a6989586621679458092] ([a6989586621679458092], [a6989586621679458092]) -> Type) (SplitAtSym0 a6989586621679458092) l Source # | |
type Apply Nat (TyFun a6989586621679458078 [a6989586621679458078] -> Type) (ReplicateSym0 a6989586621679458078) l Source # | |
type Apply Nat (TyFun (NonEmpty a6989586621679729633) [a6989586621679729633] -> Type) (TakeSym0 a6989586621679729633) l Source # | |
type Apply Nat (TyFun (NonEmpty a6989586621679729632) [a6989586621679729632] -> Type) (DropSym0 a6989586621679729632) l Source # | |
type Apply Nat (TyFun (NonEmpty a6989586621679729631) ([a6989586621679729631], [a6989586621679729631]) -> Type) (SplitAtSym0 a6989586621679729631) l Source # | |
type Apply a6989586621679458104 (TyFun [a6989586621679458104] [Nat] -> Type) (ElemIndicesSym0 a6989586621679458104) l Source # | |
type Apply a6989586621679458105 (TyFun [a6989586621679458105] (Maybe Nat) -> Type) (ElemIndexSym0 a6989586621679458105) l Source # | |
type Apply [a] Nat (LengthSym0 a) l Source # | |
type Apply (NonEmpty a) Nat (LengthSym0 a) l Source # | |
type Apply [a] [Nat] (FindIndicesSym1 a l1) l2 Source # | |
type Apply [a] [Nat] (ElemIndicesSym1 a l1) l2 Source # | |
type Apply [a] (Maybe Nat) (FindIndexSym1 a l1) l2 Source # | |
type Apply [a] (Maybe Nat) (ElemIndexSym1 a l1) l2 Source # | |
type Apply [a6989586621679458076] (TyFun Nat a6989586621679458076 -> Type) ((:!!$) a6989586621679458076) l Source # | |
type Apply (NonEmpty a6989586621679729611) (TyFun Nat a6989586621679729611 -> Type) ((:!!$) a6989586621679729611) l Source # | |
type Apply (TyFun a6989586621679458102 Bool -> Type) (TyFun [a6989586621679458102] [Nat] -> Type) (FindIndicesSym0 a6989586621679458102) l Source # | |
type Apply (TyFun a6989586621679458103 Bool -> Type) (TyFun [a6989586621679458103] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679458103) l Source # | |
(Kind) This is the kind of type-level symbols. Declared here because class IP needs it
SingKind Symbol | Since: 4.9.0.0 |
KnownSymbol a => SingI Symbol a | Since: 4.9.0.0 |
SuppressUnusedWarnings (TyFun Symbol Constraint -> *) KnownSymbolSym0 Source # | |
data Sing Symbol | |
type DemoteRep Symbol | |
type Demote 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 arg1 arg2 Source # | |
type (:<=) Symbol arg1 arg2 Source # | |
type (:>) Symbol arg1 arg2 Source # | |
type (:>=) Symbol arg1 arg2 Source # | |
type Max Symbol arg1 arg2 Source # | |
type Min Symbol arg1 arg2 Source # | |
type Apply Symbol Constraint KnownSymbolSym0 l 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 [a] Source # | |
data Sing (Maybe a) Source # | |
data Sing (NonEmpty a) Source # | |
data Sing (Either a b) Source # | |
data Sing (a, b) Source # | |
data Sing ((~>) k1 k2) Source # | |
data Sing (a, b, c) Source # | |
data Sing (a, b, c, d) Source # | |
data Sing (a, b, c, d, e) Source # | |
data Sing (a, b, c, d, e, f) Source # | |
data Sing (a, b, c, d, e, f, g) 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
data KnownNatSym0 (l :: TyFun Nat Constraint) Source #
SuppressUnusedWarnings (TyFun Nat Constraint -> *) KnownNatSym0 Source # | |
type Apply Nat Constraint KnownNatSym0 l Source # | |
type KnownNatSym1 (t :: Nat) = KnownNat t Source #
class KnownSymbol (n :: Symbol) #
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
data KnownSymbolSym0 (l :: TyFun Symbol Constraint) Source #
type KnownSymbolSym1 (t :: Symbol) = KnownSymbol t Source #
symbolVal :: KnownSymbol n => proxy n -> String #
Since: 4.7.0.0
Orphan instances
Eq Nat Source # | |
Eq Symbol Source # | This bogus instance is helpful for people who want to define functions over Symbols that will only be used at the type level or as singletons. |
Num Nat Source # | This bogus |
Ord Nat Source # | |
Ord Symbol Source # | |