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

Description

Multiplicative groups of integers modulo m.

Synopsis

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.

Primitive roots

data PrimitiveRoot m Source #

PrimitiveRoot m is a type which is only inhabited by primitive roots of m.

Instances

Instances details
Show (PrimitiveRoot m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

Eq (PrimitiveRoot m) Source # 
Instance details

Defined in Math.NumberTheory.Moduli.Multiplicative

unPrimitiveRoot :: PrimitiveRoot m -> MultMod m Source #

Extract primitive root value.

isPrimitiveRoot :: (Integral a, UniqueFactorisation a) => CyclicGroup a m -> Mod m -> Maybe (PrimitiveRoot m) Source #

Check whether a given modular residue is a primitive root.

>>> :set -XDataKinds
>>> import Data.Maybe
>>> isPrimitiveRoot (fromJust cyclicGroup) (1 :: Mod 13)
Nothing
>>> isPrimitiveRoot (fromJust cyclicGroup) (2 :: Mod 13)
Just (PrimitiveRoot {unPrimitiveRoot = MultMod {multElement = (2 `modulo` 13)}})

discreteLogarithm :: CyclicGroup Integer m -> PrimitiveRoot m -> MultMod m -> Natural Source #

Computes the discrete logarithm. Currently uses a combination of the baby-step giant-step method and Pollard's rho algorithm, with Bach reduction.

>>> :set -XDataKinds
>>> import Data.Maybe
>>> let cg = fromJust cyclicGroup :: CyclicGroup Integer 13
>>> let rt = fromJust (isPrimitiveRoot cg 2)
>>> let x  = fromJust (isMultElement 11)
>>> discreteLogarithm cg rt x
7