arithmoi-0.8.0.0: Efficient basic number-theoretic functions.

Copyright(c) 2017 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
StabilityProvisional
PortabilityNon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.Moduli.Class

Contents

Description

Safe modular arithmetic with modulo on type level.

Synopsis

Known modulo

data Mod (m :: Nat) Source #

Wrapper for residues modulo m.

Mod 3 :: Mod 10 stands for the class of integers, congruent to 3 modulo 10 (…−17, −7, 3, 13, 23…). The modulo is stored on type level, so it is impossible, for example, to add up by mistake residues with different moduli.

>>> :set -XDataKinds
>>> (3 :: Mod 10) + (4 :: Mod 12)
error: Couldn't match type ‘12’ with ‘10’...
>>> (3 :: Mod 10) + 8
(1 `modulo` 10)

Note that modulo cannot be negative.

Instances
KnownNat m => Bounded (Mod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

Methods

minBound :: Mod m #

maxBound :: Mod m #

Enum (Mod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

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

Eq (Mod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

Methods

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

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

KnownNat m => Fractional (Mod m) Source #

Beware that division by residue, which is not coprime with the modulo, will result in runtime error. Consider using invertMod instead.

Instance details

Defined in Math.NumberTheory.Moduli.Class

Methods

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

recip :: Mod m -> Mod m #

fromRational :: Rational -> Mod m #

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

Defined in Math.NumberTheory.Moduli.Class

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 #

Ord (Mod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

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 => Show (Mod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

Methods

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

show :: Mod m -> String #

showList :: [Mod m] -> ShowS #

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 :: KnownNat m => Mod m -> Maybe (Mod m) Source #

Computes the modular inverse, if the residue is coprime with the modulo.

>>> :set -XDataKinds
>>> invertMod (3 :: Mod 10)
Just (7 `modulo` 10) -- because 3 * 7 = 1 :: Mod 10
>>> invertMod (4 :: Mod 10)
Nothing

powMod :: (KnownNat m, Integral a) => Mod m -> a -> Mod m Source #

Drop-in replacement for ^, with much better performance.

>>> :set -XDataKinds
>>> powMod (3 :: Mod 10) 4
> (1 `modulo` 10)

(^%) :: (KnownNat m, Integral a) => Mod m -> a -> Mod m infixr 8 Source #

Infix synonym of powMod.

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 toMultElement to construct.

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

Defined in Math.NumberTheory.Moduli.Class

Eq (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

Methods

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

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

Ord (MultMod m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

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 #

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

Defined in Math.NumberTheory.Moduli.Class

Methods

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

show :: MultMod m -> String #

showList :: [MultMod m] -> ShowS #

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

Defined in Math.NumberTheory.Moduli.Class

Methods

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

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

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

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

Defined in Math.NumberTheory.Moduli.Class

Methods

mempty :: MultMod m #

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

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

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

Defined in Math.NumberTheory.Moduli.Class

Methods

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

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

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

Num SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

Show SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Class

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)
Just (7 `modulo` 10) -- because 3 * 7 = 1 :: Mod 10
>>> invertMod (4 `modulo` 10)
Nothing
>>> 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