base-4.16.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: base-4.10.0.0

Synopsis

Nat Kind

data Natural Source #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Instances

Instances details
Data Natural #

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural Source #

toConstr :: Natural -> Constr Source #

dataTypeOf :: Natural -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Natural) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) Source #

gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

Bits Natural #

Since: base-4.8.0

Instance details

Defined in GHC.Bits

Enum Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Ix Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Ix

Num Natural #

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Read Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

Integral Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Real Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Show Natural #

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

PrintfArg Natural #

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

Eq Natural 
Instance details

Defined in GHC.Num.Natural

Ord Natural 
Instance details

Defined in GHC.Num.Natural

KnownNat n => HasResolution (n :: Nat) #

For example, Fixed 1000 will give you a Fixed with a resolution of 1000.

Instance details

Defined in Data.Fixed

Methods

resolution :: p n -> Integer Source #

type Compare (a :: Natural) (b :: Natural) # 
Instance details

Defined in Data.Type.Ord

type Compare (a :: Natural) (b :: Natural) = CmpNat a b

type Nat = Natural Source #

A type synonym for Natural.

Prevously, this was an opaque data type, but it was changed to a type synonym since base-4.15.0.0@.

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: base-4.7.0.0

Minimal complete definition

natSing

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

Since: base-4.10.0.0

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

Since: base-4.10.0.0

data SomeNat Source #

This type represents unknown type-level natural numbers.

Since: base-4.10.0.0

Constructors

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

Instances

Instances details
Read SomeNat #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Show SomeNat #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Eq SomeNat #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Ord SomeNat #

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

someNatVal :: Natural -> SomeNat Source #

Convert an integer into an unknown type-level natural.

Since: base-4.10.0.0

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

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

Since: base-4.7.0.0

Functions on type literals

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

Comparison (<=) of comparable types, as a constraint. @since 4.16.0.0

type (<=?) m n = OrdCond (Compare m n) 'True 'True 'False infix 4 Source #

Comparison (<=) of comparable types, as a function. @since 4.16.0.0

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

Addition of type-level naturals.

Since: base-4.7.0.0

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

Multiplication of type-level naturals.

Since: base-4.7.0.0

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

Exponentiation of type-level naturals.

Since: base-4.7.0.0

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

Subtraction of type-level naturals.

Since: base-4.7.0.0

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

Comparison of type-level naturals, as a function.

Since: base-4.7.0.0

cmpNat :: forall a b proxy1 proxy2. (KnownNat a, KnownNat b) => proxy1 a -> proxy2 b -> OrderingI a b Source #

Like sameNat, but if the numbers aren't equal, this additionally provides proof of LT or GT. @since 4.16.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: base-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: base-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: base-4.11.0.0