| Copyright | (c) 2017 Andrew Lelechenko | 
|---|---|
| License | MIT | 
| Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Math.NumberTheory.Moduli.Class
Description
Safe modular arithmetic with modulo on type level.
Synopsis
- data Mod (m :: Nat)
- getVal :: forall (m :: Nat). Integer
- getNatVal :: forall (m :: Nat). Mod m -> Natural
- getMod :: forall (m :: Nat). KnownNat m => Mod m -> Integer
- getNatMod :: forall (m :: Nat). KnownNat m => Mod m -> Natural
- invertMod :: forall (m :: Nat). KnownNat m => Mod m -> Maybe (Mod m)
- powMod :: forall (m :: Nat) a. (KnownNat m, Integral a) => Mod m -> a -> Mod m
- (^%) :: forall (m :: Nat) a. (KnownNat m, Integral a) => Mod m -> a -> Mod m
- data MultMod (m :: Nat)
- multElement :: MultMod m -> Mod m
- isMultElement :: forall (m :: Nat). KnownNat m => Mod m -> Maybe (MultMod m)
- invertGroup :: forall (m :: Nat). KnownNat m => MultMod m -> MultMod m
- data SomeMod where
- modulo :: Integer -> Natural -> SomeMod
- invertSomeMod :: SomeMod -> Maybe SomeMod
- powSomeMod :: Integral a => SomeMod -> a -> SomeMod
- class KnownNat (n :: Nat)
Known modulo
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
Instances details
No validation checks are performed; reading untrusted data may corrupt internal invariants.
Instance details
Defined in Data.Mod
Methods
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 ()
No validation checks are performed; reading untrusted data may corrupt internal invariants.
Instance details
Defined in Data.Mod
Methods
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))
No validation checks are performed; reading untrusted data may corrupt internal invariants.
Instance details
Defined in Data.Mod
Wrapping behaviour, similar to
 the existing instance Read  Int .
Division by a residue, which is not
 coprime
 with the modulus, throws DivideByZero .
 Consider using invertMod  for non-prime moduli.
No validation checks are performed; reading untrusted data may corrupt internal invariants.
Instance details
Defined in Data.Mod
Methods
sizeOfType# :: Proxy (Mod m) -> Int# #
alignmentOfType# :: Proxy (Mod m) -> Int# #
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 #
Mod  m is not even an
 integral domain for
 composite m,
 much less a Euclidean domain.
The instance is lawful only for
 prime m, otherwise
 we try to do our best:
 quot  x yz such that x == y * z,
 rem  is not always 0, and both can throw DivideByZero .
Mod  m is not even an
 integral domain for
 composite m,
 much less a field.
The instance is lawful only for
 prime m, otherwise
 division by a residue, which is not
 coprime
 with the modulus, throws DivideByZero .
 Consider using invertMod  for non-prime moduli.
Instance details
Defined in Data.Mod
Mod  m is not even an
 integral domain for
 composite m,
 much less a GCD domain.
 However, gcd  and lcm  are still meaningful
 even for composite m, corresponding to a sum and an intersection of
 ideals.
The instance is lawful only for
 prime m, otherwise
 divide  x yJust z such that x == y * z.
No validation checks are performed; reading untrusted data may corrupt internal invariants.
Instance details
Defined in Data.Mod
Unboxed vectors of Mod  cause more nursery allocations
 than boxed ones, but reduce pressure on the garbage collector,
 especially for large vectors.
Unboxed vectors of Mod  cause more nursery allocations
 than boxed ones, but reduce pressure on the garbage collector,
 especially for large vectors.
getVal :: forall (m :: Nat). Mod m -> Integer Source #
The canonical representative of the residue class, always between 0 and m-1 inclusively.
getNatVal :: forall (m :: Nat). Mod m -> Natural Source #
The canonical representative of the residue class, always between 0 and m-1 inclusively.
getMod :: forall (m :: Nat). KnownNat m => Mod m -> Integer Source #
Linking type and value levels: extract modulo m as a value.
getNatMod :: forall (m :: Nat). KnownNat m => Mod m -> Natural Source #
Linking type and value levels: extract modulo m as a value.
powMod :: forall (m :: Nat) a. (KnownNat m, Integral a) => Mod m -> a -> Mod m Source #
Synonym of (^%) .
(^%) :: forall (m :: Nat) a. (KnownNat m, Integral a) => Mod m -> a -> Mod m infixr 8 #
Drop-in replacement for ^  with much 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
Multiplicative group
data MultMod (m :: Nat) Source #
This type represents elements of the multiplicative group mod m, i.e.
 those elements which are coprime to m. Use isMultElement to construct.
Instances
Instances details
Instance details
Defined in Math.NumberTheory.Moduli.Multiplicative
multElement :: MultMod m -> Mod m Source #
Unwrap a residue.
isMultElement :: forall (m :: Nat). KnownNat m => Mod m -> Maybe (MultMod m) Source #
Attempt to construct a multiplicative group element.
invertGroup :: forall (m :: Nat). KnownNat m => MultMod m -> MultMod m Source #
For elements of the multiplicative group, we can safely perform the inverse without needing to worry about failure.
Unknown modulo
This type represents residues with unknown modulo and rational numbers. One can freely combine them in arithmetic expressions, but each operation will spend time on modulo's recalculation:
>>>2 `modulo` 10 + 4 `modulo` 15(1 `modulo` 5)>>>(2 `modulo` 10) * (4 `modulo` 15)(3 `modulo` 5)>>>import Data.Ratio>>>2 `modulo` 10 + fromRational (3 % 7)(1 `modulo` 10)>>>2 `modulo` 10 * fromRational (3 % 7)(8 `modulo` 10)
If performance is crucial, it is recommended to extract Mod m for further processing
 by pattern matching. E. g.,
case modulo n m of
 SomeMod k -> process k -- Here k has type Mod m
 InfMod{} -> error "impossible"Instances
Instances details
Instance details
Defined in Math.NumberTheory.Moduli.SomeMod
Beware that division by residue, which is not coprime with the modulo,
 will result in runtime error. Consider using invertSomeMod  instead.
Instance details
Defined in Math.NumberTheory.Moduli.SomeMod
Instance details
Defined in Math.NumberTheory.Moduli.SomeMod
modulo :: Integer -> Natural -> SomeMod infixl 7 Source #
Create modular value by representative of residue class and modulo.
 One can use the result either directly (via functions from Num  and Fractional ),
 or deconstruct it by pattern matching. Note that modulo  never returns InfMod .
invertSomeMod :: SomeMod -> Maybe SomeMod Source #
Computes the inverse value, if it exists.
>>>invertSomeMod (3 `modulo` 10) -- because 3 * 7 = 1 :: Mod 10Just (7 `modulo` 10)>>>invertSomeMod (4 `modulo` 10)Nothing>>>import Data.Ratio>>>invertSomeMod (fromRational (2 % 5))Just 5 % 2
powSomeMod :: Integral a => SomeMod -> a -> SomeMod Source #
Drop-in replacement for ^ , with much better performance.
 When -O is enabled, there is a rewrite rule, which specialises ^  to powSomeMod .
>>>powSomeMod (3 `modulo` 10) 4(1 `modulo` 10)