| Copyright | (C) 2015-2024 mniip |
|---|---|
| License | BSD3 |
| Maintainer | mniip <mniip@mniip.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Finite.Internal.Integral
Description
Synopsis
- class Integral a => SaneIntegral a where
- type Limited a (n :: Nat) = LeqMaybe n (Limit a)
- class KnownIntegral a (n :: Nat)
- intVal :: forall n a proxy. KnownIntegral a n => proxy n -> a
- withIntegral :: forall a n r proxy1 proxy2. (SaneIntegral a, KnownIntegral a n) => proxy1 a -> proxy2 n -> (KnownNat n => r) -> r
- withLimited :: forall a n r proxy1 proxy2. (SaneIntegral a, KnownIntegral a n) => proxy1 a -> proxy2 n -> (Limited a n => r) -> r
- newtype Finite a (n :: Nat) = Finite a
- finite :: forall n a. (SaneIntegral a, KnownIntegral a n) => a -> Finite a n
- getFinite :: forall n a. Finite a n -> a
Documentation
class Integral a => SaneIntegral a where Source #
A class of datatypes that faithfully represent a sub-range of Integer
that includes 0. A valid instance must obey the following laws:
fromInteger must be a retract of toInteger:
fromInteger (toInteger a) == a
Restricted to the range [0, (with Limit]Nothing understood as positive
infinity), fromInteger must be an inverse of toInteger:
limited i ==> toInteger (fromInteger i) == i
where:
limited i = case limit of
Just l -> 0 <= i && i <= l
Nothing -> 0 <= iWARNING: violating the above constraint in particular breaks type safety.
The implementations of Ord, Enum, Num, Integral must be compatible
with that of Integer, whenever all arguments and results fall within
[0, , for example:Limit]
limited i && limited j && limited k && (i * j == k) ==> (fromInteger i * fromInteger j == fromInteger k)
Methods modAdd, modSub, and modMul implement modular addition,
multiplication, and subtraction. The default implementation is via Integer,
but a faster implementation can be provided instead. If provided, the
implementation must be correct for moduli in range [1, .Limit]
WARNING: a naive implementaton is prone to arithmetic overflow and may
produce invalid results for moduli close to Limit.
Minimal complete definition
Nothing
Methods
modAdd :: a -> a -> a -> a Source #
modSub :: a -> a -> a -> a Source #
modMul :: a -> a -> a -> a Source #
unsafeWithLimited :: proxy1 a -> proxy2 n -> (Limited a n => r) -> r Source #
Instances
type Limited a (n :: Nat) = LeqMaybe n (Limit a) Source #
Ensures that the value of n is representable in type a (which should be
a SaneIntegral).
class KnownIntegral a (n :: Nat) Source #
This class asserts that the value of n is known at runtime, and that it
is representable in type a (which should be a SaneIntegral).
At runtime it acts like an implicit parameter of type a, much like
KnownNat is an implicit parameter of type Integer.
Minimal complete definition
intVal_
Instances
| (SaneIntegral a, Limited a n, KnownNat n) => KnownIntegral a n Source # | |
Defined in Data.Finite.Internal.Integral | |
intVal :: forall n a proxy. KnownIntegral a n => proxy n -> a Source #
Reflect a type-level number into a term.
withIntegral :: forall a n r proxy1 proxy2. (SaneIntegral a, KnownIntegral a n) => proxy1 a -> proxy2 n -> (KnownNat n => r) -> r Source #
Recover a KnownNat constraint from a KnownIntegral constraint.
withLimited :: forall a n r proxy1 proxy2. (SaneIntegral a, KnownIntegral a n) => proxy1 a -> proxy2 n -> (Limited a n => r) -> r Source #
Recover a Limited constraint from a KnownIntegral constraint.
newtype Finite a (n :: Nat) Source #
Finite number type. The type is inhabited by exactly Finite a nn
values from type a, in the range [0, n) including 0 but excluding n.
a must be an instance of SaneIntegral to use this type. Invariants:
getFinite x < intVal x
getFinite x >= 0
Constructors
| Finite a |
Instances
finite :: forall n a. (SaneIntegral a, KnownIntegral a n) => a -> Finite a n Source #
Convert an a into a , throwing an error if the input is out
of bounds.Finite a