Copyright | (c) 2017-2022 Andrew Lelechenko |
---|---|
License | MIT |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Modular arithmetic, promoting moduli to the type level, with an emphasis on performance. Originally part of the arithmoi package.
This module supports only moduli, which fit into Word
.
Use the (slower) Data.Mod module for handling arbitrary-sized moduli.
Documentation
This data type represents integers modulo m, equipped with useful instances.
For example, 3 :: Mod
10 stands for the class of integers
congruent to \( 3 \bmod 10 \colon \ldots {−17}, −7, 3, 13, 23 \ldots \)
>>>
:set -XDataKinds
>>>
3 + 8 :: Mod 10 -- 3 + 8 = 11 ≡ 1 (mod 10)
1
Note: Mod
0 has no inhabitants, eventhough \( \mathbb{Z}/0\mathbb{Z} \) is technically isomorphic to \( \mathbb{Z} \).
Instances
Vector Vector (Mod m) Source # | No validation checks are performed; reading untrusted data may corrupt internal invariants. |
Defined in Data.Mod.Word basicUnsafeFreeze :: Mutable Vector s (Mod m) -> ST s (Vector (Mod m)) # basicUnsafeThaw :: Vector (Mod m) -> ST s (Mutable Vector s (Mod m)) # basicLength :: Vector (Mod m) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Mod m) -> Vector (Mod m) # basicUnsafeIndexM :: Vector (Mod m) -> Int -> Box (Mod m) # basicUnsafeCopy :: Mutable Vector s (Mod m) -> Vector (Mod m) -> ST s () # | |
MVector MVector (Mod m) Source # | No validation checks are performed; reading untrusted data may corrupt internal invariants. |
Defined in Data.Mod.Word basicLength :: MVector s (Mod m) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Mod m) -> MVector s (Mod m) # basicOverlaps :: MVector s (Mod m) -> MVector s (Mod m) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (Mod m)) # basicInitialize :: MVector s (Mod m) -> ST s () # basicUnsafeReplicate :: Int -> Mod m -> ST s (MVector s (Mod m)) # basicUnsafeRead :: MVector s (Mod m) -> Int -> ST s (Mod m) # basicUnsafeWrite :: MVector s (Mod m) -> Int -> Mod m -> ST s () # basicClear :: MVector s (Mod m) -> ST s () # basicSet :: MVector s (Mod m) -> Mod m -> ST s () # basicUnsafeCopy :: MVector s (Mod m) -> MVector s (Mod m) -> ST s () # basicUnsafeMove :: MVector s (Mod m) -> MVector s (Mod m) -> ST s () # basicUnsafeGrow :: MVector s (Mod m) -> Int -> ST s (MVector s (Mod m)) # | |
Storable (Mod m) Source # | No validation checks are performed; reading untrusted data may corrupt internal invariants. |
KnownNat m => Bounded (Mod m) Source # | |
KnownNat m => Enum (Mod m) Source # | |
Generic (Mod m) Source # | |
KnownNat m => Num (Mod m) Source # | |
KnownNat m => Read (Mod m) Source # | Wrapping behaviour, similar to
the existing |
KnownNat m => Fractional (Mod m) Source # | Division by a residue, which is not
coprime
with the modulus, throws |
KnownNat m => Real (Mod m) Source # | |
Defined in Data.Mod.Word toRational :: Mod m -> Rational # | |
Show (Mod m) Source # | |
NFData (Mod m) Source # | |
Defined in Data.Mod.Word | |
Eq (Mod m) Source # | |
Ord (Mod m) Source # | |
Prim (Mod m) Source # | No validation checks are performed; reading untrusted data may corrupt internal invariants. |
Defined in Data.Mod.Word alignment# :: Mod m -> Int# # indexByteArray# :: ByteArray# -> Int# -> Mod m # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Mod m #) # writeByteArray# :: MutableByteArray# s -> Int# -> Mod m -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Mod m -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Mod m # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Mod m #) # writeOffAddr# :: Addr# -> Int# -> Mod m -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Mod m -> State# s -> State# s # | |
KnownNat m => Euclidean (Mod m) Source # |
The instance is lawful only for
prime |
KnownNat m => Field (Mod m) Source # |
The instance is lawful only for
prime |
Defined in Data.Mod.Word | |
KnownNat m => GcdDomain (Mod m) Source # |
The instance is lawful only for
prime |
KnownNat m => Ring (Mod m) Source # | |
Defined in Data.Mod.Word | |
KnownNat m => Semiring (Mod m) Source # | |
Unbox (Mod m) Source # | No validation checks are performed; reading untrusted data may corrupt internal invariants. |
Defined in Data.Mod.Word | |
newtype MVector s (Mod m) Source # | |
type Rep (Mod m) Source # | |
Defined in Data.Mod.Word | |
newtype Vector (Mod m) Source # | |
unMod :: Mod m -> Word Source #
The canonical representative of the residue class, always between 0 and \( m - 1 \) (inclusively).
>>>
:set -XDataKinds
>>>
-1 :: Mod 10
9
(^%) :: (KnownNat m, Integral a) => Mod m -> a -> Mod m infixr 8 Source #
Drop-in replacement for ^
with a bit better performance.
Negative powers are allowed, but may throw DivideByZero
, if an argument
is not coprime with the modulus.
>>>
:set -XDataKinds
>>>
3 ^% 4 :: Mod 10 -- 3 ^ 4 = 81 ≡ 1 (mod 10)
1>>>
3 ^% (-1) :: Mod 10 -- 3 * 7 = 21 ≡ 1 (mod 10)
7>>>
4 ^% (-1) :: Mod 10 -- 4 and 10 are not coprime
(*** Exception: divide by zero