numeric-kinds-0.2.0: Type-level numeric types and classes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Kinds.Num

Description

Type-level equivalent of a subset of Num.

This provides "kindclasses" (actually open type families) with functionality analogous to that provided by the Num typeclass. Since type-level typeclasses don't exist, instead we translate each would-be method to its own open type family; then "instances" are implemented by providing clauses for each type family "method". Unfortunately this means we can't group methods into classes that must be implemented all-or-none, but in practice this seems to be okay.

Synopsis
  • type family FromNat (n :: Nat) :: k
  • type family ToInteger (n :: k) :: Integer
  • type family (x :: k) + (y :: k) :: k
  • type family (x :: k) - (y :: k) :: k
  • type family (x :: k) * (y :: k) :: k

Conversions

type family FromNat (n :: Nat) :: k Source #

Type-level numeric conversion from Nat. Like fromInteger in Num.

Instances

Instances details
type FromNat n Source # 
Instance details

Defined in Kinds.Num

type FromNat n = n
type FromNat n Source # 
Instance details

Defined in Kinds.Integer

type FromNat n = 'Pos n

type family ToInteger (n :: k) :: Integer Source #

Type-level conversion to Integer. Like toInteger in Integral.

Instances

Instances details
type ToInteger (n :: Nat) Source # 
Instance details

Defined in Kinds.Num

type ToInteger (n :: Nat) = 'Pos n
type ToInteger (n :: Integer) Source # 
Instance details

Defined in Kinds.Integer

type ToInteger (n :: Integer) = n

Arithmetic

type family (x :: k) + (y :: k) :: k Source #

Type-level addition "kindclass".

Instances

Instances details
type (x :: Nat) + (y :: Nat) Source # 
Instance details

Defined in Kinds.Num

type (x :: Nat) + (y :: Nat) = x + y
type (x :: Integer) + (y :: Integer) Source # 
Instance details

Defined in Kinds.Integer

type (x :: Integer) + (y :: Integer) = AddInteger x y

type family (x :: k) - (y :: k) :: k Source #

Type-level subtraction "kindclass".

Instances

Instances details
type (x :: Nat) - (y :: Nat) Source # 
Instance details

Defined in Kinds.Num

type (x :: Nat) - (y :: Nat) = x - y
type (x :: Integer) - (y :: Integer) Source # 
Instance details

Defined in Kinds.Integer

type (x :: Integer) - (y :: Integer) = SubInteger x y

type family (x :: k) * (y :: k) :: k Source #

Type-level multiplication "kindclass".

Instances

Instances details
type (x :: Nat) * (y :: Nat) Source # 
Instance details

Defined in Kinds.Num

type (x :: Nat) * (y :: Nat) = x * y
type (x :: Integer) * (y :: Integer) Source # 
Instance details

Defined in Kinds.Integer

type (x :: Integer) * (y :: Integer) = MulInteger x y