singletons-2.2: A framework for generating singleton types

Copyright(C) 2014 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (eir@cis.upenn.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.TypeLits

Contents

Description

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.

Synopsis

Documentation

data Nat :: * #

(Kind) This is the kind of type-level natural numbers.

Instances

SNum Nat Source # 
SEnum Nat Source # 
PNum Nat (Proxy * Nat) Source # 

Associated Types

type ((Proxy * Nat) :+ (arg :: Proxy * Nat)) (arg :: Proxy * Nat) :: a Source #

type ((Proxy * Nat) :- (arg :: Proxy * Nat)) (arg :: Proxy * Nat) :: a Source #

type ((Proxy * Nat) :* (arg :: Proxy * Nat)) (arg :: Proxy * Nat) :: a Source #

type Negate (Proxy * Nat) (arg :: Proxy * Nat) :: a Source #

type Abs (Proxy * Nat) (arg :: Proxy * Nat) :: a Source #

type Signum (Proxy * Nat) (arg :: Proxy * Nat) :: a Source #

type FromInteger (Proxy * Nat) (arg :: Nat) :: a Source #

PEnum Nat (Proxy * Nat) Source # 

Associated Types

type Succ (Proxy * Nat) (arg :: Proxy * Nat) :: a Source #

type Pred (Proxy * Nat) (arg :: Proxy * Nat) :: a Source #

type ToEnum (Proxy * Nat) (arg :: Nat) :: a Source #

type FromEnum (Proxy * Nat) (arg :: Proxy * Nat) :: Nat Source #

type EnumFromTo (Proxy * Nat) (arg :: Proxy * Nat) (arg :: Proxy * Nat) :: [a] Source #

type EnumFromThenTo (Proxy * Nat) (arg :: Proxy * Nat) (arg :: Proxy * Nat) (arg :: Proxy * Nat) :: [a] 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 # 

Methods

suppressUnusedWarnings :: Proxy (FindIndexSym1 a1627953316) t -> () Source #

SuppressUnusedWarnings ((TyFun a1627953315 Bool -> Type) -> TyFun [a1627953315] [Nat] -> *) (FindIndicesSym1 a1627953315) Source # 

Methods

suppressUnusedWarnings :: Proxy (FindIndicesSym1 a1627953315) t -> () Source #

SuppressUnusedWarnings ([a1627953289] -> TyFun Nat a1627953289 -> *) ((:!!$$) a1627953289) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:!!$$) a1627953289) t -> () Source #

SuppressUnusedWarnings (Nat -> TyFun [a1627953305] ([a1627953305], [a1627953305]) -> *) (SplitAtSym1 a1627953305) Source # 

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym1 a1627953305) t -> () Source #

SuppressUnusedWarnings (Nat -> TyFun [a1627953307] [a1627953307] -> *) (TakeSym1 a1627953307) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeSym1 a1627953307) t -> () Source #

SuppressUnusedWarnings (Nat -> TyFun [a1627953306] [a1627953306] -> *) (DropSym1 a1627953306) Source # 

Methods

suppressUnusedWarnings :: Proxy (DropSym1 a1627953306) t -> () Source #

SuppressUnusedWarnings (Nat -> TyFun a1627953291 [a1627953291] -> *) (ReplicateSym1 a1627953291) Source # 

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym1 a1627953291) t -> () Source #

SuppressUnusedWarnings (a1627953318 -> TyFun [a1627953318] (Maybe Nat) -> *) (ElemIndexSym1 a1627953318) Source # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym1 a1627953318) t -> () Source #

SuppressUnusedWarnings (a1627953317 -> TyFun [a1627953317] [Nat] -> *) (ElemIndicesSym1 a1627953317) Source # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym1 a1627953317) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627953316 Bool -> Type) (TyFun [a1627953316] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a1627953316) Source # 

Methods

suppressUnusedWarnings :: Proxy (FindIndexSym0 a1627953316) t -> () Source #

SuppressUnusedWarnings (TyFun (TyFun a1627953315 Bool -> Type) (TyFun [a1627953315] [Nat] -> Type) -> *) (FindIndicesSym0 a1627953315) Source # 

Methods

suppressUnusedWarnings :: Proxy (FindIndicesSym0 a1627953315) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953292] Nat -> *) (LengthSym0 a1627953292) Source # 

Methods

suppressUnusedWarnings :: Proxy (LengthSym0 a1627953292) t -> () Source #

SuppressUnusedWarnings (TyFun [a1627953289] (TyFun Nat a1627953289 -> Type) -> *) ((:!!$) a1627953289) Source # 

Methods

suppressUnusedWarnings :: Proxy ((:!!$) a1627953289) t -> () Source #

SuppressUnusedWarnings (TyFun Nat (TyFun [a1627953305] ([a1627953305], [a1627953305]) -> Type) -> *) (SplitAtSym0 a1627953305) Source # 

Methods

suppressUnusedWarnings :: Proxy (SplitAtSym0 a1627953305) t -> () Source #

SuppressUnusedWarnings (TyFun Nat (TyFun [a1627953307] [a1627953307] -> Type) -> *) (TakeSym0 a1627953307) Source # 

Methods

suppressUnusedWarnings :: Proxy (TakeSym0 a1627953307) t -> () Source #

SuppressUnusedWarnings (TyFun Nat (TyFun [a1627953306] [a1627953306] -> Type) -> *) (DropSym0 a1627953306) Source # 

Methods

suppressUnusedWarnings :: Proxy (DropSym0 a1627953306) t -> () Source #

SuppressUnusedWarnings (TyFun Nat (TyFun a1627953291 [a1627953291] -> Type) -> *) (ReplicateSym0 a1627953291) Source # 

Methods

suppressUnusedWarnings :: Proxy (ReplicateSym0 a1627953291) t -> () Source #

SuppressUnusedWarnings (TyFun Nat a1627817219 -> *) (FromIntegerSym0 a1627817219) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromIntegerSym0 a1627817219) t -> () Source #

SuppressUnusedWarnings (TyFun Nat a1627864213 -> *) (ToEnumSym0 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (ToEnumSym0 a1627864213) t -> () Source #

SuppressUnusedWarnings (TyFun a1627864213 Nat -> *) (FromEnumSym0 a1627864213) Source # 

Methods

suppressUnusedWarnings :: Proxy (FromEnumSym0 a1627864213) t -> () Source #

SuppressUnusedWarnings (TyFun a1627953318 (TyFun [a1627953318] (Maybe Nat) -> Type) -> *) (ElemIndexSym0 a1627953318) Source # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndexSym0 a1627953318) t -> () Source #

SuppressUnusedWarnings (TyFun a1627953317 (TyFun [a1627953317] [Nat] -> Type) -> *) (ElemIndicesSym0 a1627953317) Source # 

Methods

suppressUnusedWarnings :: Proxy (ElemIndicesSym0 a1627953317) t -> () Source #

type DemoteRep Nat Source # 
data Sing Nat Source # 
data Sing Nat where
type Negate Nat a Source # 
type Negate Nat a = Error Nat Symbol "Cannot negate a natural number"
type Abs Nat a Source # 
type Abs Nat a = a
type Signum Nat a Source # 
type Signum Nat a
type FromInteger Nat a Source # 
type FromInteger Nat a = a
type Succ Nat a0 Source # 
type Succ Nat a0
type Pred Nat a0 Source # 
type Pred Nat a0
type ToEnum Nat a0 Source # 
type ToEnum Nat a0
type FromEnum Nat a0 Source # 
type FromEnum Nat a0
type (==) Nat a b 
type (==) Nat a b = EqNat a b
type (:==) Nat a b Source # 
type (:==) Nat a b = (==) Nat a b
type (:/=) Nat x y Source # 
type (:/=) Nat x y = Not ((:==) Nat x y)
type Compare Nat a b Source # 
type Compare Nat a b = CmpNat a b
type (:<) Nat arg0 arg1 Source # 
type (:<) Nat arg0 arg1
type (:<=) Nat arg0 arg1 Source # 
type (:<=) Nat arg0 arg1
type (:>) Nat arg0 arg1 Source # 
type (:>) Nat arg0 arg1
type (:>=) Nat arg0 arg1 Source # 
type (:>=) Nat arg0 arg1
type Max Nat arg0 arg1 Source # 
type Max Nat arg0 arg1
type Min Nat arg0 arg1 Source # 
type Min Nat arg0 arg1
type (:+) Nat a b Source # 
type (:+) Nat a b = (+) a b
type (:-) Nat a b Source # 
type (:-) Nat a b = (-) a b
type (:*) Nat a b Source # 
type (:*) Nat a b = * a b
type EnumFromTo Nat a0 a1 Source # 
type EnumFromTo Nat a0 a1
type EnumFromThenTo Nat a0 a1 a2 Source # 
type EnumFromThenTo Nat a0 a1 a2
type Apply Nat Nat ((:^$$) l1) l0 Source # 
type Apply Nat Nat ((:^$$) l1) l0 = (:^$$$) l1 l0
type Apply Nat k2 (FromIntegerSym0 k2) l0 Source # 
type Apply Nat k2 (FromIntegerSym0 k2) l0 = FromIntegerSym1 k2 l0
type Apply Nat k2 (ToEnumSym0 k2) l0 Source # 
type Apply Nat k2 (ToEnumSym0 k2) l0 = ToEnumSym1 k2 l0
type Apply a1627864213 Nat (FromEnumSym0 a1627864213) l0 Source # 
type Apply a1627864213 Nat (FromEnumSym0 a1627864213) l0 = FromEnumSym1 a1627864213 l0
type Apply Nat a1627953289 ((:!!$$) a1627953289 l1) l0 Source # 
type Apply Nat a1627953289 ((:!!$$) a1627953289 l1) l0 = (:!!$$$) a1627953289 l1 l0
type Apply Nat (TyFun Nat Nat -> *) (:^$) l0 Source # 
type Apply Nat (TyFun Nat Nat -> *) (:^$) l0 = (:^$$) l0
type Apply Nat (TyFun [a1627953305] ([a1627953305], [a1627953305]) -> Type) (SplitAtSym0 a1627953305) l0 Source # 
type Apply Nat (TyFun [a1627953305] ([a1627953305], [a1627953305]) -> Type) (SplitAtSym0 a1627953305) l0 = SplitAtSym1 a1627953305 l0
type Apply Nat (TyFun [a1627953307] [a1627953307] -> Type) (TakeSym0 a1627953307) l0 Source # 
type Apply Nat (TyFun [a1627953307] [a1627953307] -> Type) (TakeSym0 a1627953307) l0 = TakeSym1 a1627953307 l0
type Apply Nat (TyFun [a1627953306] [a1627953306] -> Type) (DropSym0 a1627953306) l0 Source # 
type Apply Nat (TyFun [a1627953306] [a1627953306] -> Type) (DropSym0 a1627953306) l0 = DropSym1 a1627953306 l0
type Apply Nat (TyFun a1627953291 [a1627953291] -> Type) (ReplicateSym0 a1627953291) l0 Source # 
type Apply Nat (TyFun a1627953291 [a1627953291] -> Type) (ReplicateSym0 a1627953291) l0 = ReplicateSym1 a1627953291 l0
type Apply a1627953318 (TyFun [a1627953318] (Maybe Nat) -> Type) (ElemIndexSym0 a1627953318) l0 Source # 
type Apply a1627953318 (TyFun [a1627953318] (Maybe Nat) -> Type) (ElemIndexSym0 a1627953318) l0 = ElemIndexSym1 a1627953318 l0
type Apply a1627953317 (TyFun [a1627953317] [Nat] -> Type) (ElemIndicesSym0 a1627953317) l0 Source # 
type Apply a1627953317 (TyFun [a1627953317] [Nat] -> Type) (ElemIndicesSym0 a1627953317) l0 = ElemIndicesSym1 a1627953317 l0
type Apply [a1627953292] Nat (LengthSym0 a1627953292) l0 Source # 
type Apply [a1627953292] Nat (LengthSym0 a1627953292) l0 = LengthSym1 a1627953292 l0
type Apply [a1627953318] (Maybe Nat) (ElemIndexSym1 a1627953318 l1) l0 Source # 
type Apply [a1627953318] (Maybe Nat) (ElemIndexSym1 a1627953318 l1) l0 = ElemIndexSym2 a1627953318 l1 l0
type Apply [a1627953316] (Maybe Nat) (FindIndexSym1 a1627953316 l1) l0 Source # 
type Apply [a1627953316] (Maybe Nat) (FindIndexSym1 a1627953316 l1) l0 = FindIndexSym2 a1627953316 l1 l0
type Apply [a1627953317] [Nat] (ElemIndicesSym1 a1627953317 l1) l0 Source # 
type Apply [a1627953317] [Nat] (ElemIndicesSym1 a1627953317 l1) l0 = ElemIndicesSym2 a1627953317 l1 l0
type Apply [a1627953315] [Nat] (FindIndicesSym1 a1627953315 l1) l0 Source # 
type Apply [a1627953315] [Nat] (FindIndicesSym1 a1627953315 l1) l0 = FindIndicesSym2 a1627953315 l1 l0
type Apply [a1627953289] (TyFun Nat a1627953289 -> Type) ((:!!$) a1627953289) l0 Source # 
type Apply [a1627953289] (TyFun Nat a1627953289 -> Type) ((:!!$) a1627953289) l0 = (:!!$$) a1627953289 l0
type Apply (TyFun a1627953316 Bool -> Type) (TyFun [a1627953316] (Maybe Nat) -> Type) (FindIndexSym0 a1627953316) l0 Source # 
type Apply (TyFun a1627953316 Bool -> Type) (TyFun [a1627953316] (Maybe Nat) -> Type) (FindIndexSym0 a1627953316) l0 = FindIndexSym1 a1627953316 l0
type Apply (TyFun a1627953315 Bool -> Type) (TyFun [a1627953315] [Nat] -> Type) (FindIndicesSym0 a1627953315) l0 Source # 
type Apply (TyFun a1627953315 Bool -> Type) (TyFun [a1627953315] [Nat] -> Type) (FindIndicesSym0 a1627953315) l0 = FindIndicesSym1 a1627953315 l0

data Symbol :: * #

(Kind) This is the kind of type-level symbols. Declared here because class IP needs it

Instances

KnownSymbol a => SingI Symbol a 

Methods

sing :: Sing a a

SingKind Symbol (KProxy Symbol) 

Associated Types

type DemoteRep (KProxy Symbol) (kparam :: KProxy (KProxy Symbol)) :: *

Methods

fromSing :: Sing (KProxy Symbol) a -> DemoteRep (KProxy Symbol) kparam

data Sing Symbol 
data Sing Symbol where
type DemoteRep Symbol Source # 
data Sing Symbol Source # 
data Sing Symbol where
type (==) Symbol a b 
type (==) Symbol a b = EqSymbol a b
type (:==) Symbol a b Source # 
type (:==) Symbol a b = (==) Symbol a b
type (:/=) Symbol x y Source # 
type (:/=) Symbol x y = Not ((:==) Symbol x y)
type Compare Symbol a b Source # 
type Compare Symbol a b = CmpSymbol a b
type (:<) Symbol arg0 arg1 Source # 
type (:<) Symbol arg0 arg1
type (:<=) Symbol arg0 arg1 Source # 
type (:<=) Symbol arg0 arg1
type (:>) Symbol arg0 arg1 Source # 
type (:>) Symbol arg0 arg1
type (:>=) Symbol arg0 arg1 Source # 
type (:>=) Symbol arg0 arg1
type Max Symbol arg0 arg1 Source # 
type Max Symbol arg0 arg1
type Min Symbol arg0 arg1 Source # 
type Min Symbol arg0 arg1
type DemoteRep Symbol (KProxy Symbol) 
type DemoteRep Symbol (KProxy Symbol) = String

data family Sing (a :: k) Source #

The singleton kind-indexed data family.

Instances

data Sing Bool Source # 
data Sing Bool where
data Sing Ordering Source # 
data Sing * Source # 
data Sing * where
data Sing Nat Source # 
data Sing Nat where
data Sing Symbol Source # 
data Sing Symbol where
data Sing () Source # 
data Sing () where
data Sing [a0] Source # 
data Sing [a0] where
data Sing (Maybe a0) Source # 
data Sing (Maybe a0) where
data Sing (NonEmpty a0) Source # 
data Sing (NonEmpty a0) where
data Sing (Either a0 b0) Source # 
data Sing (Either a0 b0) where
data Sing (a0, b0) Source # 
data Sing (a0, b0) where
data Sing ((~>) k1 k2) Source # 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a0, b0, c0) Source # 
data Sing (a0, b0, c0) where
data Sing (a0, b0, c0, d0) Source # 
data Sing (a0, b0, c0, d0) where
data Sing (a0, b0, c0, d0, e0) Source # 
data Sing (a0, b0, c0, d0, e0) where
data Sing (a0, b0, c0, d0, e0, f0) Source # 
data Sing (a0, b0, c0, d0, e0, f0) where
data Sing (a0, b0, c0, d0, e0, f0, g0) Source # 
data Sing (a0, b0, c0, d0, e0, f0, g0) where

type SNat x = Sing x Source #

Kind-restricted synonym for Sing for Nats

type SSymbol x = Sing x Source #

Kind-restricted synonym for Sing for Symbols

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.

data ErrorSym0 l Source #

Instances

SuppressUnusedWarnings (TyFun k01627810588 k1627810590 -> *) (ErrorSym0 k01627810588 k1627810590) Source # 

Methods

suppressUnusedWarnings :: Proxy (ErrorSym0 k01627810588 k1627810590) t -> () Source #

type Apply k01627810588 k2 (ErrorSym0 k01627810588 k2) l0 Source # 
type Apply k01627810588 k2 (ErrorSym0 k01627810588 k2) l0 = ErrorSym1 k01627810588 k2 l0

type ErrorSym1 t = Error t Source #

sError :: Sing (str :: Symbol) -> a Source #

The singleton for error

class KnownNat n #

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

Minimal complete definition

natSing

natVal :: KnownNat n => proxy n -> Integer #

Since: 4.7.0.0

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

Minimal complete definition

symbolSing

symbolVal :: KnownSymbol n => proxy n -> String #

Since: 4.7.0.0

type (:^) a b = a ^ b infixr 8 Source #

data l :^$$ l Source #

Instances

type (:^$$$) t t = (:^) t t Source #

Orphan instances

Num Nat Source # 

Methods

(+) :: Nat -> Nat -> Nat #

(-) :: Nat -> Nat -> Nat #

(*) :: Nat -> Nat -> Nat #

negate :: Nat -> Nat #

abs :: Nat -> Nat #

signum :: Nat -> Nat #

fromInteger :: Integer -> Nat #