mod-0.2.0.1: Fast type-safe modular arithmetic
Copyright(c) 2017-2022 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Mod.Word

Description

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.

Synopsis

Documentation

data Mod (m :: Nat) Source #

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
Vector Vector (Mod m) Source #

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

Instance details

Defined in Data.Mod.Word

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 #

MVector MVector (Mod m) Source #

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

Instance details

Defined in Data.Mod.Word

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

Storable (Mod m) Source #

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

Instance details

Defined in Data.Mod.Word

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) Source # 
Instance details

Defined in Data.Mod.Word

Methods

minBound :: Mod m #

maxBound :: Mod m #

KnownNat m => Enum (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

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) Source # 
Instance details

Defined in Data.Mod.Word

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) Source # 
Instance details

Defined in Data.Mod.Word

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

Wrapping behaviour, similar to the existing instance Read Int.

Instance details

Defined in Data.Mod.Word

KnownNat m => Fractional (Mod m) Source #

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.Word

Methods

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

recip :: Mod m -> Mod m #

fromRational :: Rational -> Mod m #

KnownNat m => Real (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

Methods

toRational :: Mod m -> Rational #

Show (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

Methods

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

show :: Mod m -> String #

showList :: [Mod m] -> ShowS #

NFData (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

Methods

rnf :: Mod m -> () #

Eq (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

Methods

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

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

Ord (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

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 #

Prim (Mod m) Source #

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

Instance details

Defined in Data.Mod.Word

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

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.Word

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

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.Word

KnownNat m => GcdDomain (Mod m) Source #

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.Word

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) Source # 
Instance details

Defined in Data.Mod.Word

Methods

negate :: Mod m -> Mod m #

KnownNat m => Semiring (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

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 #

Unbox (Mod m) Source #

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

Instance details

Defined in Data.Mod.Word

newtype MVector s (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

newtype MVector s (Mod m) = MV_Mod (MVector s Word)
type Rep (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

type Rep (Mod m) = D1 ('MetaData "Mod" "Data.Mod.Word" "mod-0.2.0.1-77HdehbY7w4DZp8RwhUH2U" 'True) (C1 ('MetaCons "Mod" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))
newtype Vector (Mod m) Source # 
Instance details

Defined in Data.Mod.Word

newtype Vector (Mod m) = V_Mod (Vector Word)

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

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

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

(^%) :: (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