Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Arithmetic.Types
Contents
Synopsis
- data Nat (n :: Nat)
- data Nat# :: Nat -> TYPE 'IntRep
- data WithNat :: (Nat -> Type) -> Type where
- data Difference :: Nat -> Nat -> Type where
- Difference :: forall a b c. Nat c -> ((c + b) :=: a) -> Difference a b
- data Fin :: Nat -> Type where
- data Fin# :: Nat -> TYPE 'IntRep
- data Fin32# :: Nat -> TYPE 'Int32Rep
- data MaybeFin# :: Nat -> TYPE 'IntRep
- pattern MaybeFinJust# :: Fin# n -> MaybeFin# n
- pattern MaybeFinNothing# :: MaybeFin# n
- data (<) :: Nat -> Nat -> Type
- data (<=) :: Nat -> Nat -> Type
- data (<#) :: Nat -> Nat -> TYPE ('TupleRep '[])
- data (<=#) :: Nat -> Nat -> TYPE ('TupleRep '[])
- data (:=:) :: Nat -> Nat -> Type
- data (:=:#) :: Nat -> Nat -> TYPE ('TupleRep '[])
Documentation
A value-level representation of a natural number n
.
data Difference :: Nat -> Nat -> Type where Source #
Proof that the first argument can be expressed as the sum of the second argument and some other natural number.
Constructors
Difference :: forall a b c. Nat c -> ((c + b) :=: a) -> Difference a b |
data Fin :: Nat -> Type where Source #
A finite set of n
elements. 'Fin n = { 0 .. n - 1 }'
data Fin# :: Nat -> TYPE 'IntRep Source #
Finite numbers without the overhead of carrying around a proof.
Maybe Fin
data MaybeFin# :: Nat -> TYPE 'IntRep Source #
Either a Fin#
or Nothing. Internally, this uses negative
one to mean Nothing.
pattern MaybeFinJust# :: Fin# n -> MaybeFin# n Source #
pattern MaybeFinNothing# :: MaybeFin# n Source #
Infix Operators
data (<) :: Nat -> Nat -> Type infix 4 Source #
Proof that the first argument is strictly less than the second argument.
data (<=) :: Nat -> Nat -> Type infix 4 Source #
Proof that the first argument is less than or equal to the second argument.