numeric-kinds-0.1.0.0: Type-level numeric types, classes, and instances.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Kinds.Num

Description

Type-level Ord and Num.

This provides "kindclasses" (actually open type families) with functionality analogous to that provided by the typeclasses Ord and Num. 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

Comparisons

type family Cmp (x :: k) (y :: k) :: Ordering Source #

Type-level Ord "kindclass".

Note this has an invisible dependent k parameter that makes the textually-identical instances for different kinds actually different. Neat!

Instances

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

Defined in Kinds.Num

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

Defined in Kinds.Integer

type Cmp (x :: Integer) (y :: Integer) = CmpInteger x y

type (<?) x y = IsLT (Cmp x y) infix 4 Source #

type (<=?) x y = IsLE (Cmp x y) infix 4 Source #

type (==?) x y = IsEQ (Cmp x y) infix 4 Source #

type (/=?) x y = IsNE (Cmp x y) infix 4 Source #

type (>=?) x y = IsGE (Cmp x y) infix 4 Source #

type (>?) x y = IsGT (Cmp x y) infix 4 Source #

Inequality Constraints

type (<) x y = Cmp x y ~ 'LT infix 4 Source #

type (<=) x y = Proven (x <=? y) infix 4 Source #

type (==) x y = Cmp x y ~ 'EQ infix 4 Source #

type (/=) x y = Proven (x /=? y) infix 4 Source #

type (>=) x y = Proven (x >=? y) infix 4 Source #

type (>) x y = Cmp x y ~ 'GT infix 4 Source #

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

Utility

type Proven b = b ~ 'True Source #

Turns a type-level Bool into a Constraint that it's True.

type family IsLT o where ... Source #

Test whether an Ordering is LT.

Equations

IsLT 'LT = 'True 
IsLT o = 'False 

type family IsLE o where ... Source #

Test whether an Ordering is LT or EQ.

Equations

IsLE 'GT = 'False 
IsLE o = 'True 

type family IsGT o where ... Source #

Test whether an Ordering is GT.

Equations

IsGT 'GT = 'True 
IsGT o = 'False 

type family IsGE o where ... Source #

Test whether an Ordering is GT or EQ.

Equations

IsGE 'LT = 'False 
IsGE o = 'True 

type family IsEQ o where ... Source #

Test whether an Ordering is EQ.

Equations

IsEQ 'EQ = 'True 
IsEQ o = 'False 

type family IsNE o where ... Source #

Test whether an Ordering is LT or GT.

Equations

IsNE 'EQ = 'False 
IsNE o = 'True