base-4.13.0.0: Basic libraries
Safe HaskellTrustworthy
LanguageHaskell2010

GHC.TypeNats

Description

This module is an internal GHC module. It declares the constants used in the implementation of type-level natural numbers. The programmer interface for working with type-level naturals should be defined in a separate library.

Since: 4.10.0.0

Synopsis

Nat Kind

data Nat #

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

Linking type and value level

class KnownNat (n :: Nat) Source #

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 :: forall n proxy. KnownNat n => proxy n -> Natural Source #

Since: 4.10.0.0

natVal' :: forall n. KnownNat n => Proxy# n -> Natural Source #

Since: 4.10.0.0

data SomeNat Source #

This type represents unknown type-level natural numbers.

Since: 4.10.0.0

Constructors

forall n.KnownNat n => SomeNat (Proxy n) 

Instances

Instances details
Eq SomeNat Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeNats

Methods

(==) :: SomeNat -> SomeNat -> Bool #

(/=) :: SomeNat -> SomeNat -> Bool #

Ord SomeNat Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeNats

Read SomeNat Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeNats

Show SomeNat Source #

Since: 4.7.0.0

Instance details

Defined in GHC.TypeNats

someNatVal :: Natural -> SomeNat Source #

Convert an integer into an unknown type-level natural.

Since: 4.10.0.0

sameNat :: (KnownNat a, KnownNat b) => Proxy a -> Proxy b -> Maybe (a :~: b) Source #

We either get evidence that this function was instantiated with the same type-level numbers, or Nothing.

Since: 4.7.0.0

Functions on type literals

type (<=) x y = (x <=? y) ~ 'True infix 4 Source #

Comparison of type-level naturals, as a constraint.

Since: 4.7.0.0

type family (m :: Nat) <=? (n :: Nat) :: Bool infix 4 Source #

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.

type family (m :: Nat) + (n :: Nat) :: Nat infixl 6 Source #

Addition of type-level naturals.

Since: 4.7.0.0

type family (m :: Nat) * (n :: Nat) :: Nat infixl 7 Source #

Multiplication of type-level naturals.

Since: 4.7.0.0

type family (m :: Nat) ^ (n :: Nat) :: Nat infixr 8 Source #

Exponentiation of type-level naturals.

Since: 4.7.0.0

type family (m :: Nat) - (n :: Nat) :: Nat infixl 6 Source #

Subtraction of type-level naturals.

Since: 4.7.0.0

type family CmpNat (m :: Nat) (n :: Nat) :: Ordering Source #

Comparison of type-level naturals, as a function.

Since: 4.7.0.0

type family Div (m :: Nat) (n :: Nat) :: Nat infixl 7 Source #

Division (round down) of natural numbers. Div x 0 is undefined (i.e., it cannot be reduced).

Since: 4.11.0.0

type family Mod (m :: Nat) (n :: Nat) :: Nat infixl 7 Source #

Modulus of natural numbers. Mod x 0 is undefined (i.e., it cannot be reduced).

Since: 4.11.0.0

type family Log2 (m :: Nat) :: Nat Source #

Log base 2 (round down) of natural numbers. Log 0 is undefined (i.e., it cannot be reduced).

Since: 4.11.0.0