| Copyright | (C) 2014 Richard Eisenberg | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | Ryan Scott | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Singletons.TypeLits
Description
Defines and exports singletons useful for the Nat and Symbol kinds.
Synopsis
- data Nat
- data Symbol
- type family Sing
- data SNat n = KnownNat n => SNat
- data SSymbol n = KnownSymbol n => SSym
- withKnownNat :: Sing n -> (KnownNat n => r) -> r
- withKnownSymbol :: Sing n -> (KnownSymbol n => r) -> r
- type family Error str where ...
- sError :: HasCallStack => Sing (str :: Symbol) -> a
- type family ErrorWithoutStackTrace str where ...
- sErrorWithoutStackTrace :: Sing (str :: Symbol) -> a
- type family Undefined where ...
- sUndefined :: HasCallStack => a
- class KnownNat (n :: Nat)
- natVal :: forall (n :: Nat) proxy. KnownNat n => proxy n -> Natural
- class KnownSymbol (n :: Symbol)
- symbolVal :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> String
- type family (a :: Nat) ^ (b :: Nat) :: Nat where ...
- (%^) :: Sing a -> Sing b -> Sing (a ^ b)
- type family (a :: Nat) <=? (b :: Nat) :: Bool where ...
- (%<=?) :: Sing a -> Sing b -> Sing (a <=? b)
- type family Log2 (a :: Nat) :: Nat where ...
- sLog2 :: Sing x -> Sing (Log2 x)
- type family Div (a :: Nat) (b :: Nat) :: Nat where ...
- sDiv :: Sing x -> Sing y -> Sing (Div x y)
- type family Mod (a :: Nat) (b :: Nat) :: Nat where ...
- sMod :: Sing x -> Sing y -> Sing (Mod x y)
- type family DivMod a a where ...
- sDivMod :: Sing x -> Sing y -> Sing (DivMod x y)
- type family Quot a a where ...
- sQuot :: Sing x -> Sing y -> Sing (Quot x y)
- type family Rem a a where ...
- sRem :: Sing x -> Sing y -> Sing (Rem x y)
- type family QuotRem a a where ...
- sQuotRem :: Sing x -> Sing y -> Sing (QuotRem x y)
- data ErrorSym0 a6989586621679472252
- type ErrorSym1 (a6989586621679472252 :: k0) = Error a6989586621679472252 :: k
- data ErrorWithoutStackTraceSym0 a6989586621679472488
- type ErrorWithoutStackTraceSym1 (a6989586621679472488 :: k0) = ErrorWithoutStackTrace a6989586621679472488 :: k
- type UndefinedSym0 = Undefined :: k
- data KnownNatSym0 a6989586621679491988
- type KnownNatSym1 (a6989586621679491988 :: Nat) = KnownNat a6989586621679491988 :: Constraint
- data KnownSymbolSym0 a6989586621679491990
- type KnownSymbolSym1 (a6989586621679491990 :: Symbol) = KnownSymbol a6989586621679491990 :: Constraint
- data (^@#@$) a6989586621679472866
- data a6989586621679472866 ^@#@$$ a6989586621679472867
- type (^@#@$$$) (a6989586621679472866 :: Nat) (a6989586621679472867 :: Nat) = (^) a6989586621679472866 a6989586621679472867 :: Nat
- data (<=?@#@$) a6989586621679473158
- data a6989586621679473158 <=?@#@$$ a6989586621679473159
- type (<=?@#@$$$) (a6989586621679473158 :: Nat) (a6989586621679473159 :: Nat) = (<=?) a6989586621679473158 a6989586621679473159 :: Bool
- data Log2Sym0 a6989586621679492472
- type Log2Sym1 (a6989586621679492472 :: Nat) = Log2 a6989586621679492472 :: Nat
- data DivSym0 a6989586621679492680
- data DivSym1 a6989586621679492680 a6989586621679492681
- type DivSym2 (a6989586621679492680 :: Nat) (a6989586621679492681 :: Nat) = Div a6989586621679492680 a6989586621679492681 :: Nat
- data ModSym0 a6989586621679493016
- data ModSym1 a6989586621679493016 a6989586621679493017
- type ModSym2 (a6989586621679493016 :: Nat) (a6989586621679493017 :: Nat) = Mod a6989586621679493016 a6989586621679493017 :: Nat
- data DivModSym0 a6989586621679493510
- data DivModSym1 a6989586621679493510 a6989586621679493511
- type DivModSym2 (a6989586621679493510 :: Nat) (a6989586621679493511 :: Nat) = DivMod a6989586621679493510 a6989586621679493511 :: (Nat, Nat)
- data QuotSym0 a6989586621679493492
- data QuotSym1 a6989586621679493492 a6989586621679493493
- type QuotSym2 (a6989586621679493492 :: Nat) (a6989586621679493493 :: Nat) = Quot a6989586621679493492 a6989586621679493493 :: Nat
- data RemSym0 a6989586621679493481
- data RemSym1 a6989586621679493481 a6989586621679493482
- type RemSym2 (a6989586621679493481 :: Nat) (a6989586621679493482 :: Nat) = Rem a6989586621679493481 a6989586621679493482 :: Nat
- data QuotRemSym0 a6989586621679493503
- data QuotRemSym1 a6989586621679493503 a6989586621679493504
- type QuotRemSym2 (a6989586621679493503 :: Nat) (a6989586621679493504 :: Nat) = QuotRem a6989586621679493503 a6989586621679493504 :: (Nat, Nat)
Documentation
(Kind) This is the kind of type-level natural numbers.
Instances
(Kind) This is the kind of type-level symbols. Declared here because class IP needs it
Instances
The singleton kind-indexed type family.
Instances
Constructors
| KnownSymbol n => SSym | 
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 where ... Source #
The promotion of error. This version is more poly-kinded for
 easier use.
type family ErrorWithoutStackTrace str where ... Source #
The promotion of errorWithoutStackTrace. This version is more
 poly-kinded for easier use.
sErrorWithoutStackTrace :: Sing (str :: Symbol) -> a Source #
The singleton for errorWithoutStackTrace.
sUndefined :: HasCallStack => a Source #
The singleton for undefined.
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: base-4.7.0.0
Minimal complete definition
natSing
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: base-4.7.0.0
Minimal complete definition
symbolSing
symbolVal :: forall (n :: Symbol) proxy. KnownSymbol n => proxy n -> String #
Since: base-4.7.0.0
type family (a :: Nat) ^ (b :: Nat) :: Nat where ... infixr 8 #
Exponentiation of type-level naturals.
Since: base-4.7.0.0
type family (a :: Nat) <=? (b :: Nat) :: Bool where ... infix 4 #
Comparison of type-level naturals, as a function.
NOTE: The functionality for this function should be subsumed
by CmpNat, so this might go away in the future.
Please let us know, if you encounter discrepancies between the two. 
(%<=?) :: Sing a -> Sing b -> Sing (a <=? b) infix 4 Source #
The singleton analogue of <=?
Note that, because of historical reasons in GHC's Nat API, <=?
 is incompatible (unification-wise) with <= and the PEq, SEq,
 POrd, and SOrd instances for Nat.  (a  does not
 imply anything about <=? b) ~ 'Truea  or any other <= bPEq / POrd
 relationships.
(Be aware that <= in the paragraph above refers to <= from the
 POrd typeclass, exported from Data.Singletons.Prelude.Ord, and not
 the <= from GHC.TypeNats.  The latter is simply a type alias for
 (a .)<=? b) ~ 'True
This is provided here for the sake of completeness and for compatibility
 with libraries with APIs built around <=?.  New code should use
 CmpNat, exposed through this library through the POrd and SOrd
 instances for Nat.
type family Log2 (a :: Nat) :: Nat where ... #
Log base 2 (round down) of natural numbers.
 Log 0 is undefined (i.e., it cannot be reduced).
Since: base-4.11.0.0
type family Div (a :: Nat) (b :: Nat) :: Nat where ... infixl 7 #
Division (round down) of natural numbers.
 Div x 0 is undefined (i.e., it cannot be reduced).
Since: base-4.11.0.0
type family Mod (a :: Nat) (b :: Nat) :: Nat where ... infixl 7 #
Modulus of natural numbers.
 Mod x 0 is undefined (i.e., it cannot be reduced).
Since: base-4.11.0.0
type family QuotRem a a where ... Source #
Equations
| QuotRem a_6989586621679493496 a_6989586621679493498 = Apply (Apply DivModSym0 a_6989586621679493496) a_6989586621679493498 | 
Defunctionalization symbols
data ErrorSym0 a6989586621679472252 Source #
Instances
data ErrorWithoutStackTraceSym0 a6989586621679472488 Source #
Instances
| SingI (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # | |
| Defined in Data.Singletons.TypeLits.Internal Methods | |
| SuppressUnusedWarnings (ErrorWithoutStackTraceSym0 :: TyFun k0 k -> Type) Source # | |
| Defined in Data.Singletons.TypeLits.Internal Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ErrorWithoutStackTraceSym0 :: TyFun k0 k2 -> Type) (a6989586621679472488 :: k0) Source # | |
| Defined in Data.Singletons.TypeLits.Internal type Apply (ErrorWithoutStackTraceSym0 :: TyFun k0 k2 -> Type) (a6989586621679472488 :: k0) = ErrorWithoutStackTraceSym1 a6989586621679472488 :: k2 | |
type ErrorWithoutStackTraceSym1 (a6989586621679472488 :: k0) = ErrorWithoutStackTrace a6989586621679472488 :: k Source #
type UndefinedSym0 = Undefined :: k Source #
data KnownNatSym0 a6989586621679491988 Source #
Instances
| SuppressUnusedWarnings KnownNatSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply KnownNatSym0 (a6989586621679491988 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
type KnownNatSym1 (a6989586621679491988 :: Nat) = KnownNat a6989586621679491988 :: Constraint Source #
data KnownSymbolSym0 a6989586621679491990 Source #
Instances
| SuppressUnusedWarnings KnownSymbolSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply KnownSymbolSym0 (a6989586621679491990 :: Symbol) Source # | |
| Defined in Data.Singletons.TypeLits | |
type KnownSymbolSym1 (a6989586621679491990 :: Symbol) = KnownSymbol a6989586621679491990 :: Constraint Source #
data (^@#@$) a6989586621679472866 infixr 8 Source #
Instances
| SingI (^@#@$) Source # | |
| SuppressUnusedWarnings (^@#@$) Source # | |
| Defined in Data.Singletons.TypeLits.Internal Methods suppressUnusedWarnings :: () Source # | |
| type Apply (^@#@$) (a6989586621679472866 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits.Internal | |
data a6989586621679472866 ^@#@$$ a6989586621679472867 infixr 8 Source #
Instances
| SingI x => SingI ((^@#@$$) x :: TyFun Nat Nat -> Type) Source # | |
| SuppressUnusedWarnings ((^@#@$$) a6989586621679472866 :: TyFun Nat Nat -> Type) Source # | |
| Defined in Data.Singletons.TypeLits.Internal Methods suppressUnusedWarnings :: () Source # | |
| type Apply ((^@#@$$) a6989586621679472866 :: TyFun Nat Nat -> Type) (a6989586621679472867 :: Nat) Source # | |
type (^@#@$$$) (a6989586621679472866 :: Nat) (a6989586621679472867 :: Nat) = (^) a6989586621679472866 a6989586621679472867 :: Nat infixr 8 Source #
data (<=?@#@$) a6989586621679473158 infix 4 Source #
Instances
| SingI (<=?@#@$) Source # | |
| SuppressUnusedWarnings (<=?@#@$) Source # | |
| Defined in Data.Singletons.TypeLits.Internal Methods suppressUnusedWarnings :: () Source # | |
| type Apply (<=?@#@$) (a6989586621679473158 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits.Internal | |
data a6989586621679473158 <=?@#@$$ a6989586621679473159 infix 4 Source #
Instances
| SingI x => SingI ((<=?@#@$$) x :: TyFun Nat Bool -> Type) Source # | |
| Defined in Data.Singletons.TypeLits.Internal Methods sing :: Sing ((<=?@#@$$) x) Source # | |
| SuppressUnusedWarnings ((<=?@#@$$) a6989586621679473158 :: TyFun Nat Bool -> Type) Source # | |
| Defined in Data.Singletons.TypeLits.Internal Methods suppressUnusedWarnings :: () Source # | |
| type Apply ((<=?@#@$$) a6989586621679473158 :: TyFun Nat Bool -> Type) (a6989586621679473159 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits.Internal | |
type (<=?@#@$$$) (a6989586621679473158 :: Nat) (a6989586621679473159 :: Nat) = (<=?) a6989586621679473158 a6989586621679473159 :: Bool infix 4 Source #
data Log2Sym0 a6989586621679492472 Source #
Instances
| SingI Log2Sym0 Source # | |
| SuppressUnusedWarnings Log2Sym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply Log2Sym0 (a6989586621679492472 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
data DivSym0 a6989586621679492680 infixl 7 Source #
Instances
| SingI DivSym0 Source # | |
| SuppressUnusedWarnings DivSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply DivSym0 (a6989586621679492680 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
data DivSym1 a6989586621679492680 a6989586621679492681 infixl 7 Source #
Instances
| SingI x => SingI (DivSym1 x :: TyFun Nat Nat -> Type) Source # | |
| SuppressUnusedWarnings (DivSym1 a6989586621679492680 :: TyFun Nat Nat -> Type) Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DivSym1 a6989586621679492680 :: TyFun Nat Nat -> Type) (a6989586621679492681 :: Nat) Source # | |
type DivSym2 (a6989586621679492680 :: Nat) (a6989586621679492681 :: Nat) = Div a6989586621679492680 a6989586621679492681 :: Nat infixl 7 Source #
data ModSym0 a6989586621679493016 infixl 7 Source #
Instances
| SingI ModSym0 Source # | |
| SuppressUnusedWarnings ModSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply ModSym0 (a6989586621679493016 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
data ModSym1 a6989586621679493016 a6989586621679493017 infixl 7 Source #
Instances
| SingI x => SingI (ModSym1 x :: TyFun Nat Nat -> Type) Source # | |
| SuppressUnusedWarnings (ModSym1 a6989586621679493016 :: TyFun Nat Nat -> Type) Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply (ModSym1 a6989586621679493016 :: TyFun Nat Nat -> Type) (a6989586621679493017 :: Nat) Source # | |
type ModSym2 (a6989586621679493016 :: Nat) (a6989586621679493017 :: Nat) = Mod a6989586621679493016 a6989586621679493017 :: Nat infixl 7 Source #
data DivModSym0 a6989586621679493510 Source #
Instances
| SuppressUnusedWarnings DivModSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply DivModSym0 (a6989586621679493510 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
data DivModSym1 a6989586621679493510 a6989586621679493511 Source #
Instances
| SuppressUnusedWarnings (DivModSym1 a6989586621679493510 :: TyFun Nat (Nat, Nat) -> Type) Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply (DivModSym1 a6989586621679493510 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493511 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits type Apply (DivModSym1 a6989586621679493510 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493511 :: Nat) = DivModSym2 a6989586621679493510 a6989586621679493511 | |
type DivModSym2 (a6989586621679493510 :: Nat) (a6989586621679493511 :: Nat) = DivMod a6989586621679493510 a6989586621679493511 :: (Nat, Nat) Source #
data QuotSym0 a6989586621679493492 infixl 7 Source #
Instances
| SuppressUnusedWarnings QuotSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply QuotSym0 (a6989586621679493492 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
data QuotSym1 a6989586621679493492 a6989586621679493493 infixl 7 Source #
type QuotSym2 (a6989586621679493492 :: Nat) (a6989586621679493493 :: Nat) = Quot a6989586621679493492 a6989586621679493493 :: Nat infixl 7 Source #
data RemSym0 a6989586621679493481 infixl 7 Source #
Instances
| SuppressUnusedWarnings RemSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply RemSym0 (a6989586621679493481 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
data RemSym1 a6989586621679493481 a6989586621679493482 infixl 7 Source #
type RemSym2 (a6989586621679493481 :: Nat) (a6989586621679493482 :: Nat) = Rem a6989586621679493481 a6989586621679493482 :: Nat infixl 7 Source #
data QuotRemSym0 a6989586621679493503 Source #
Instances
| SuppressUnusedWarnings QuotRemSym0 Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply QuotRemSym0 (a6989586621679493503 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits | |
data QuotRemSym1 a6989586621679493503 a6989586621679493504 Source #
Instances
| SuppressUnusedWarnings (QuotRemSym1 a6989586621679493503 :: TyFun Nat (Nat, Nat) -> Type) Source # | |
| Defined in Data.Singletons.TypeLits Methods suppressUnusedWarnings :: () Source # | |
| type Apply (QuotRemSym1 a6989586621679493503 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493504 :: Nat) Source # | |
| Defined in Data.Singletons.TypeLits type Apply (QuotRemSym1 a6989586621679493503 :: TyFun Nat (Nat, Nat) -> Type) (a6989586621679493504 :: Nat) = QuotRemSym2 a6989586621679493503 a6989586621679493504 | |
type QuotRemSym2 (a6989586621679493503 :: Nat) (a6989586621679493504 :: Nat) = QuotRem a6989586621679493503 a6989586621679493504 :: (Nat, Nat) Source #
Orphan instances
| Enum Nat Source # | |
| 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 # | |
| Show Nat Source # | |
| Show Symbol Source # | |
| IsString Symbol Source # | |
| Methods fromString :: String -> Symbol # | |
| Semigroup Symbol Source # | |
| Monoid Symbol Source # | |