Safe Haskell | None |
---|---|
Language | Haskell2010 |
Arithmetic.Unsafe
Synopsis
- newtype Nat (n :: Nat) = Nat {}
- newtype Nat# (a :: Nat) :: TYPE 'IntRep where
- newtype Fin# (a :: Nat) :: TYPE 'IntRep where
- newtype MaybeFin# (a :: Nat) :: TYPE 'IntRep where
- newtype EitherFin# (a :: Nat) (b :: Nat) :: TYPE 'IntRep where
- EitherFin# :: forall (a :: Nat) (b :: Nat). Int# -> EitherFin# a b
- newtype Fin32# (a :: Nat) :: TYPE 'Int32Rep where
- newtype (a :: Nat) <# (b :: Nat) :: ZeroBitType where
- newtype (a :: Nat) <=# (b :: Nat) :: ZeroBitType where
- data (a :: Nat) < (b :: Nat) where
- data (a :: Nat) <= (b :: Nat) where
- data (a :: Nat) :=: (b :: Nat) where
- newtype (a :: Nat) :=:# (b :: Nat) :: ZeroBitType where
Documentation
newtype Fin# (a :: Nat) :: TYPE 'IntRep where Source #
Finite numbers without the overhead of carrying around a proof.
newtype MaybeFin# (a :: Nat) :: TYPE 'IntRep where Source #
Either a Fin#
or Nothing. Internally, this uses negative
one to mean Nothing.
newtype EitherFin# (a :: Nat) (b :: Nat) :: TYPE 'IntRep where Source #
Either a Fin#
bounded by the left natural or one bounded
by the right natural.
Constructors
EitherFin# :: forall (a :: Nat) (b :: Nat). Int# -> EitherFin# a b |
newtype Fin32# (a :: Nat) :: TYPE 'Int32Rep where Source #
Variant of Fin#
that only allows 32-bit integers.
data (a :: Nat) < (b :: Nat) where infix 4 Source #
Proof that the first argument is strictly less than the second argument.
data (a :: Nat) <= (b :: Nat) where infix 4 Source #
Proof that the first argument is less than or equal to the second argument.