Safe Haskell | None |
---|---|
Language | Haskell2010 |
Arithmetic.Types
Synopsis
- data Nat (n :: Nat)
- data Nat# (a :: Nat) :: TYPE 'IntRep
- data WithNat (a :: Nat -> Type) where
- data Difference (a :: Nat) (b :: Nat) where
- Difference :: forall (a :: Nat) (b :: Nat) (c :: Nat). Nat c -> ((c + b) :=: a) -> Difference a b
- data Fin (a :: Nat) where
- data Fin# (a :: Nat) :: TYPE 'IntRep
- data Fin32# (a :: Nat) :: TYPE 'Int32Rep
- data MaybeFin# (a :: Nat) :: TYPE 'IntRep
- pattern MaybeFinJust# :: Fin# n -> MaybeFin# n
- pattern MaybeFinNothing# :: MaybeFin# n
- data EitherFin# (a :: Nat) (b :: Nat) :: TYPE 'IntRep
- pattern EitherFinLeft# :: Fin# m -> EitherFin# m n
- pattern EitherFinRight# :: Fin# n -> EitherFin# m n
- data (a :: Nat) < (b :: Nat)
- data (a :: Nat) <= (b :: Nat)
- data (a :: Nat) <# (b :: Nat) :: ZeroBitType
- data (a :: Nat) <=# (b :: Nat) :: ZeroBitType
- data (a :: Nat) :=: (b :: Nat)
- data (a :: Nat) :=:# (b :: Nat) :: ZeroBitType
Documentation
A value-level representation of a natural number n
.
data Difference (a :: Nat) (b :: Nat) 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 :: Nat) (b :: Nat) (c :: Nat). Nat c -> ((c + b) :=: a) -> Difference a b |
data Fin (a :: Nat) where Source #
A finite set of n
elements. 'Fin n = { 0 .. n - 1 }'
Constructors
Fin | |
data Fin# (a :: Nat) :: TYPE 'IntRep Source #
Finite numbers without the overhead of carrying around a proof.
Maybe Fin
data MaybeFin# (a :: 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 #
Either Fin
data EitherFin# (a :: Nat) (b :: Nat) :: TYPE 'IntRep Source #
Either a Fin#
bounded by the left natural or one bounded
by the right natural.
pattern EitherFinLeft# :: Fin# m -> EitherFin# m n Source #
pattern EitherFinRight# :: Fin# n -> EitherFin# m n Source #
Infix Operators
data (a :: Nat) < (b :: Nat) infix 4 Source #
Proof that the first argument is strictly less than the second argument.
data (a :: Nat) <= (b :: Nat) infix 4 Source #
Proof that the first argument is less than or equal to the second argument.