arithmoi-0.11.0.1: Efficient basic number-theoretic functions.

Copyright(c) 2017 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.Moduli.Class

Contents

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 modulo 10: …−17, −7, 3, 13, 23…

>>> :set -XDataKinds
>>> 3 + 8 :: Mod 10
(1 `modulo` 10) -- because 3 + 8 = 11 ≡ 1 (mod 10)

Warning: division by residue, which is not coprime with the modulo, throws DivideByZero. Consider using invertMod for non-prime moduli.

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

Eq (Mod m) 
Instance details

Defined in Data.Mod

Methods

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

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

KnownNat m => Fractional (Mod m)

See the warning about division above.

Instance details

Defined in Data.Mod

Methods

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

recip :: Mod m -> Mod m #

fromRational :: Rational -> 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 #

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

Defined in Data.Mod

Methods

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

show :: Mod m -> String #

showList :: [Mod m] -> ShowS #

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 #

NFData (Mod m) 
Instance details

Defined in Data.Mod

Methods

rnf :: Mod m -> () #

KnownNat m => GcdDomain (Mod m)

See the warning about division above.

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

See the warning about division above.

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)

See the warning about division above.

Instance details

Defined in Data.Mod

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 => Ring (Mod m) 
Instance details

Defined in Data.Mod

Methods

negate :: Mod m -> Mod m #

type Rep (Mod m) 
Instance details

Defined in Data.Mod

type Rep (Mod m) = D1 (MetaData "Mod" "Data.Mod" "mod-0.1.1.0-1452mtfbkCO1WoiZ524yj5" True) (C1 (MetaCons "Mod" PrefixI True) (S1 (MetaSel (Just "unMod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))

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

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

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

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

Synonym of '(^%)'.

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

Building with -O triggers a rewrite rule ^ = ^%.

>>> :set -XDataKinds
>>> 3 ^% 4 :: Mod 10
(1 `modulo` 10) -- because 3 ^ 4 = 81 ≡ 1 (mod 10)
>>> 3 ^% (-1) :: Mod 10
(7 `modulo` 10) -- because 3 * 7 = 21 ≡ 1 (mod 10)
>>> 4 ^% (-1) :: Mod 10
(*** Exception: divide by zero -- because 4 and 10 are not coprime

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

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 #

KnownNat m => 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 #

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

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)
>>> 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.SomeMod

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

Num SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Ord SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Show SomeMod Source # 
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

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

Semiring SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Ring SomeMod Source # 
Instance details

Defined in Math.NumberTheory.Moduli.SomeMod

Methods

negate :: SomeMod -> 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)
Just (7 `modulo` 10) -- because 3 * 7 = 1 :: Mod 10
>>> invertSomeMod (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