natural-arithmetic-0.2.1.0: Arithmetic of natural numbers
Safe HaskellSafe-Inferred
LanguageHaskell2010

Arithmetic.Nat

Synopsis

Addition

plus :: Nat a -> Nat b -> Nat (a + b) Source #

Add two numbers.

plus# :: Nat# a -> Nat# b -> Nat# (a + b) Source #

Variant of plus for unboxed nats.

Subtraction

monus :: Nat a -> Nat b -> Maybe (Difference a b) Source #

Subtract the second argument from the first argument.

Division

divide :: Nat a -> Nat b -> Nat (Div a b) Source #

Divide two numbers. Rounds down (towards zero)

divideRoundingUp :: Nat a -> Nat b -> Nat (Div (a - 1) b + 1) Source #

Divide two numbers. Rounds up (away from zero)

Multiplication

times :: Nat a -> Nat b -> Nat (a * b) Source #

Multiply two numbers.

Successor

succ :: Nat a -> Nat (a + 1) Source #

The successor of a number.

succ# :: Nat# a -> Nat# (a + 1) Source #

Unlifted variant of succ.

Compare

testEqual :: Nat a -> Nat b -> Maybe (a :=: b) Source #

Are the two arguments equal to one another?

testLessThan :: Nat a -> Nat b -> Maybe (a < b) Source #

Is the first argument strictly less than the second argument?

testLessThanEqual :: Nat a -> Nat b -> Maybe (a <= b) Source #

Is the first argument less-than-or-equal-to the second argument?

testZero :: Nat a -> Either (0 :=: a) (0 < a) Source #

Is zero equal to this number or less than it?

testZero# :: Nat# a -> EitherVoid# (0 :=:# a) (0 <# a) Source #

(=?) :: Nat a -> Nat b -> Maybe (a :=: b) Source #

Infix synonym of testEqual.

(<?) :: Nat a -> Nat b -> Maybe (a < b) Source #

Infix synonym of testLessThan.

(<?#) :: Nat# a -> Nat# b -> MaybeVoid# (a <# b) Source #

(<=?) :: Nat a -> Nat b -> Maybe (a <= b) Source #

Infix synonym of testLessThanEqual.

Constants

zero :: Nat 0 Source #

The number zero.

one :: Nat 1 Source #

The number one.

two :: Nat 2 Source #

The number two.

three :: Nat 3 Source #

The number three.

constant :: forall n. KnownNat n => Nat n Source #

Use GHC's built-in type-level arithmetic to create a witness of a type-level number. This only reduces if the number is a constant.

constant# :: forall n. KnownNat n => (# #) -> Nat# n Source #

Unboxed Constants

zero# :: (# #) -> Nat# 0 Source #

The number zero. Unboxed.

one# :: (# #) -> Nat# 1 Source #

The number one. Unboxed.

Unboxed Pattern Synonyms

pattern N0# :: Nat# 0 Source #

pattern N1# :: Nat# 1 Source #

pattern N2# :: Nat# 2 Source #

pattern N3# :: Nat# 3 Source #

pattern N4# :: Nat# 4 Source #

pattern N5# :: Nat# 5 Source #

pattern N6# :: Nat# 6 Source #

pattern N7# :: Nat# 7 Source #

pattern N8# :: Nat# 8 Source #

pattern N16# :: Nat# 16 Source #

pattern N32# :: Nat# 32 Source #

pattern N64# :: Nat# 64 Source #

pattern N128# :: Nat# 128 Source #

pattern N256# :: Nat# 256 Source #

pattern N512# :: Nat# 512 Source #

pattern N1024# :: Nat# 1024 Source #

pattern N2048# :: Nat# 2048 Source #

pattern N4096# :: Nat# 4096 Source #

Convert

demote :: Nat n -> Int Source #

Extract the Int from a Nat. This is intended to be used at a boundary where a safe interface meets the unsafe primitives on top of which it is built.

unlift :: Nat n -> Nat# n Source #

lift :: Nat# n -> Nat n Source #

with :: Int -> (forall n. Nat n -> a) -> a Source #

Run a computation on a witness of a type-level number. The argument Int must be greater than or equal to zero. This is not checked. Failure to upload this invariant will lead to a segfault.

with# :: Int# -> (forall n. Nat# n -> a) -> a Source #