type-level-integers-0.0.1: Provides integers lifted to the type level

Safe HaskellSafe
LanguageHaskell2010

Data.Type.Integer

Synopsis

Documentation

data PosNat Source #

Model positive natural numbers.

Constructors

PosNatOne 
S PosNat 

Instances

data Sign Source #

Model the signum of an integer.

Constructors

Minus 
Plus 

Instances

Eq Sign Source # 

Methods

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

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

Show Sign Source # 

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

data LiftedInt Source #

Model for type level integers: they are either zero or a positive natural number together with a sign.

Constructors

LIntZero 
LInt Sign PosNat 

type family LIntSucc (k :: LiftedInt) :: LiftedInt Source #

Computes the successor for a type level integer.

type family LIntPred (k :: LiftedInt) :: LiftedInt Source #

Computes the predecessor for a type level integer.

type family LIntInvert (k :: LiftedInt) :: LiftedInt Source #

Implement additive inversion for type level integers.

type family LIntPlus (k :: LiftedInt) (l :: LiftedInt) :: LiftedInt Source #

Implement addition for type level integers.

Instances

type family LIntMinus (k :: LiftedInt) (l :: LiftedInt) :: LiftedInt Source #

Implement subtraction for type level integers.

Instances

type LIntMinus m n Source # 
type LIntMinus m n = LIntPlus m (LIntInvert n)

posNatVal :: forall n. KnownPosNat n => Proxy n -> Integer Source #

liftedIntVal :: forall i. KnownInt i => Proxy i -> Integer Source #

class KnownPosNat n Source #

Minimal complete definition

posNatSing

Instances

KnownPosNat PosNatOne Source # 

Methods

posNatSing :: SPosNat PosNatOne

KnownPosNat n => KnownPosNat (S n) Source # 

Methods

posNatSing :: SPosNat (S n)

class KnownInt n Source #

Minimal complete definition

intSing

Instances

KnownInt LIntZero Source # 

Methods

intSing :: SInt LIntZero

KnownPosNat n => KnownInt (LInt Minus n) Source # 

Methods

intSing :: SInt (LInt Minus n)

KnownPosNat n => KnownInt (LInt Plus n) Source # 

Methods

intSing :: SInt (LInt Plus n)