witness-0.6.1: values that witness types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Type.Witness.Specific.Natural

Synopsis

Documentation

class KnownNat (n :: Nat) #

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

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

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

Since: base-4.16.0.0

type family (a :: Natural) + (b :: Natural) :: Natural where ... infixl 6 #

Addition of type-level naturals.

Since: base-4.7.0.0

type family (a :: Natural) * (b :: Natural) :: Natural where ... infixl 7 #

Multiplication of type-level naturals.

Since: base-4.7.0.0

type family (a :: Natural) ^ (b :: Natural) :: Natural where ... infixr 8 #

Exponentiation of type-level naturals.

Since: base-4.7.0.0

type family (a :: Natural) - (b :: Natural) :: Natural where ... infixl 6 #

Subtraction of type-level naturals.

Since: base-4.7.0.0

type family CmpNat (a :: Natural) (b :: Natural) :: Ordering where ... #

Comparison of type-level naturals, as a function.

Since: base-4.7.0.0

type family Div (a :: Natural) (b :: Natural) :: Natural 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 :: Natural) (b :: Natural) :: Natural 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 Log2 (a :: Natural) :: Natural 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 Nat = Natural #

A type synonym for Natural.

Prevously, this was an opaque data type, but it was changed to a type synonym.

Since: base-4.16.0.0

data NaturalType bn where Source #

Constructors

MkNaturalType :: KnownNat bn => NaturalType bn 

Instances

Instances details
TestEquality NaturalType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

Methods

testEquality :: forall (a :: k) (b :: k). NaturalType a -> NaturalType b -> Maybe (a :~: b) #

TestOrder NaturalType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

Methods

testCompare :: forall (a :: k) (b :: k). NaturalType a -> NaturalType b -> WOrdering a b Source #

Representative NaturalType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

WitnessValue NaturalType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

Associated Types

type WitnessValueType NaturalType Source #

Methods

witnessToValue :: forall (t :: k). NaturalType t -> WitnessValueType NaturalType Source #

valueToWitness :: WitnessValueType NaturalType -> (forall (t :: k). NaturalType t -> r) -> r Source #

KnownNat bn => Is NaturalType (bn :: Nat) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

Show (NaturalType bn) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

AllConstraint Show NaturalType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

Methods

allConstraint :: forall (t :: kt). Dict (Show (NaturalType t)) Source #

type WitnessValueType NaturalType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Natural

type family PeanoToNatural pn where ... Source #

Equations

PeanoToNatural 'Zero = 0 
PeanoToNatural ('Succ pn) = PeanoToNatural pn + 1