arithmoi-0.13.0.0: Efficient basic number-theoretic functions.
Copyright(c) 2017 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.NumberTheory.Moduli.Class

Description

Safe modular arithmetic with modulo on type level.

Synopsis

Known modulo

data Mod (m :: Nat) #

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
KnownNat m => Vector Vector (Mod m)

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 () #

elemseq :: Vector (Mod m) -> Mod m -> b -> b #

KnownNat m => MVector MVector (Mod m)

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)) #

KnownNat m => Storable (Mod m)

No validation checks are performed; reading untrusted data may corrupt internal invariants.

Instance details

Defined in Data.Mod

Methods

sizeOf :: Mod m -> Int #

alignment :: Mod m -> Int #

peekElemOff :: Ptr (Mod m) -> Int -> IO (Mod m) #

pokeElemOff :: Ptr (Mod m) -> Int -> Mod m -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Mod m) #

pokeByteOff :: Ptr b -> Int -> Mod m -> IO () #

peek :: Ptr (Mod m) -> IO (Mod m) #

poke :: Ptr (Mod m) -> Mod m -> IO () #

KnownNat m => Bounded (Mod m) 
Instance details

Defined in Data.Mod

Methods

minBound :: Mod m #

maxBound :: Mod m #

KnownNat m => Enum (Mod m) 
Instance details

Defined in Data.Mod

Methods

succ :: Mod m -> Mod m #

pred :: Mod m -> Mod m #

toEnum :: Int -> Mod m #

fromEnum :: Mod m -> Int #

enumFrom :: Mod m -> [Mod m] #

enumFromThen :: Mod m -> Mod m -> [Mod m] #

enumFromTo :: Mod m -> Mod m -> [Mod m] #

enumFromThenTo :: Mod m -> Mod m -> Mod m -> [Mod m] #

Generic (Mod m) 
Instance details

Defined in Data.Mod

Associated Types

type Rep (Mod m) :: Type -> Type #

Methods

from :: Mod m -> Rep (Mod m) x #

to :: Rep (Mod m) x -> Mod m #

KnownNat m => Num (Mod m) 
Instance details

Defined in Data.Mod

Methods

(+) :: Mod m -> Mod m -> Mod m #

(-) :: Mod m -> Mod m -> Mod m #

(*) :: Mod m -> Mod m -> Mod m #

negate :: Mod m -> Mod m #

abs :: Mod m -> Mod m #

signum :: Mod m -> Mod m #

fromInteger :: Integer -> Mod m #

KnownNat m => Read (Mod m)

Wrapping behaviour, similar to the existing instance Read Int.

Instance details

Defined in Data.Mod

KnownNat m => Fractional (Mod m)

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

Methods

(/) :: Mod m -> Mod m -> Mod m #

recip :: Mod m -> Mod m #

fromRational :: Rational -> Mod m #

KnownNat m => Real (Mod m) 
Instance details

Defined in Data.Mod

Methods

toRational :: Mod m -> Rational #

Show (Mod m) 
Instance details

Defined in Data.Mod

Methods

showsPrec :: Int -> Mod m -> ShowS #

show :: Mod m -> String #

showList :: [Mod m] -> ShowS #

NFData (Mod m) 
Instance details

Defined in Data.Mod

Methods

rnf :: Mod m -> () #

Eq (Mod m) 
Instance details

Defined in Data.Mod

Methods

(==) :: Mod m -> Mod m -> Bool #

(/=) :: Mod m -> Mod m -> Bool #

Ord (Mod m) 
Instance details

Defined in Data.Mod

Methods

compare :: Mod m -> Mod m -> Ordering #

(<) :: Mod m -> Mod m -> Bool #

(<=) :: Mod m -> Mod m -> Bool #

(>) :: Mod m -> Mod m -> Bool #

(>=) :: Mod m -> Mod m -> Bool #

max :: Mod m -> Mod m -> Mod m #

min :: Mod m -> Mod m -> Mod m #

KnownNat m => Prim (Mod m)

No validation checks are performed; reading untrusted data may corrupt internal invariants.

Instance details

Defined in Data.Mod

Methods

sizeOf# :: 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 #

KnownNat m => Euclidean (Mod m)

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 y returns any z such that x == y * z, rem is not always 0, and both can throw DivideByZero.

Instance details

Defined in Data.Mod

Methods

quotRem :: Mod m -> Mod m -> (Mod m, Mod m) #

quot :: Mod m -> Mod m -> Mod m #

rem :: Mod m -> Mod m -> Mod m #

degree :: Mod m -> Natural #

KnownNat m => Field (Mod m)

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

KnownNat m => GcdDomain (Mod m)

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 y tries to return any Just z such that x == y * z.

Instance details

Defined in Data.Mod

Methods

divide :: Mod m -> Mod m -> Maybe (Mod m) #

gcd :: Mod m -> Mod m -> Mod m #

lcm :: Mod m -> Mod m -> Mod m #

coprime :: Mod m -> Mod m -> Bool #

KnownNat m => Ring (Mod m) 
Instance details

Defined in Data.Mod

Methods

negate :: Mod m -> Mod m #

KnownNat m => Semiring (Mod m) 
Instance details

Defined in Data.Mod

Methods

plus :: Mod m -> Mod m -> Mod m #

zero :: Mod m #

times :: Mod m -> Mod m -> Mod m #

one :: Mod m #

fromNatural :: Natural -> Mod m #

KnownNat m => Unbox (Mod m)

No validation checks are performed; reading untrusted data may corrupt internal invariants.

Instance details

Defined in Data.Mod

newtype MVector s (Mod m)

Unboxed vectors of Mod cause more nursery allocations than boxed ones, but reduce pressure on the garbage collector, especially for large vectors.

Instance details

Defined in Data.Mod

newtype MVector s (Mod m) = ModMVec (MVector s (Mod m))
type Rep (Mod m) 
Instance details

Defined in Data.Mod

type Rep (Mod m) = D1 ('MetaData "Mod" "Data.Mod" "mod-0.2.0.1-7aPyAzzZin2C0Ns1lHhIBX" 'True) (C1 ('MetaCons "Mod" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))
newtype Vector (Mod m)

Unboxed vectors of Mod cause more nursery allocations than boxed ones, but reduce pressure on the garbage collector, especially for large vectors.

Instance details

Defined in Data.Mod

newtype Vector (Mod m) = ModVec (Vector (Mod m))

getVal :: Mod m -> Integer Source #

The canonical representative of the residue class, always between 0 and m-1 inclusively.

getNatVal :: Mod m -> Natural Source #

The canonical representative of the residue class, always between 0 and m-1 inclusively.

getMod :: KnownNat m => Mod m -> Integer Source #

Linking type and value levels: extract modulo m as a value.

getNatMod :: KnownNat m => Mod m -> Natural Source #

Linking type and value levels: extract modulo m as a value.

invertMod :: forall (m :: Nat). KnownNat m => Mod m -> Maybe (Mod m) #

If an argument is coprime with the modulus, return its modular inverse. Otherwise return Nothing.

>>> :set -XDataKinds
>>> invertMod 3 :: Mod 10 -- 3 * 7 = 21 ≡ 1 (mod 10)
Just 7
>>> invertMod 4 :: Mod 10 -- 4 and 10 are not coprime
Nothing

powMod :: (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 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
KnownNat m => Monoid (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

Methods

mempty :: MultMod m #

mappend :: MultMod m -> MultMod m -> MultMod m #

mconcat :: [MultMod m] -> MultMod m #

KnownNat m => Semigroup (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

Methods

(<>) :: MultMod m -> MultMod m -> MultMod m #

sconcat :: NonEmpty (MultMod m) -> MultMod m #

stimes :: Integral b => b -> MultMod m -> MultMod m #

KnownNat m => Bounded (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

Show (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

Methods

showsPrec :: Int -> MultMod m -> ShowS #

show :: MultMod m -> String #

showList :: [MultMod m] -> ShowS #

Eq (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

Methods

(==) :: MultMod m -> MultMod m -> Bool #

(/=) :: MultMod m -> MultMod m -> Bool #

Ord (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

Methods

compare :: MultMod m -> MultMod m -> Ordering #

(<) :: MultMod m -> MultMod m -> Bool #

(<=) :: MultMod m -> MultMod m -> Bool #

(>) :: MultMod m -> MultMod m -> Bool #

(>=) :: MultMod m -> MultMod m -> Bool #

max :: MultMod m -> MultMod m -> MultMod m #

min :: MultMod m -> MultMod m -> MultMod m #

multElement :: MultMod m -> Mod m Source #

Unwrap a residue.

isMultElement :: KnownNat m => Mod m -> Maybe (MultMod m) Source #

Attempt to construct a multiplicative group element.

invertGroup :: 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

data SomeMod where Source #

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"

Constructors

SomeMod :: KnownNat m => Mod m -> SomeMod 
InfMod :: Rational -> SomeMod 

Instances

Instances details
Num SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Fractional SomeMod Source #

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

Show SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Eq SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Methods

(==) :: SomeMod -> SomeMod -> Bool #

(/=) :: SomeMod -> SomeMod -> Bool #

Ord SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Euclidean SomeMod Source #

See the warning about division above.

Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Field SomeMod Source #

See the warning about division above.

Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

GcdDomain SomeMod Source #

See the warning about division above.

Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Ring SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Methods

negate :: SomeMod -> SomeMod #

Semiring SomeMod Source # 
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 10
Just (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)

Re-exported from GHC.TypeNats.Compat

class KnownNat (n :: Nat) #

This class gives the integer associated with a type-level natural. There are instances of the class for every concrete literal: 0, 1, 2, etc.

Since: base-4.7.0.0

Minimal complete definition

natSing