| Copyright | (c) 2017 Andrew Lelechenko |
|---|---|
| License | MIT |
| Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
| Safe Haskell | None |
| Language | Haskell2010 |
Math.NumberTheory.Moduli.PrimitiveRoot
Contents
Description
Primitive roots and cyclic groups.
Synopsis
- data CyclicGroup a
- = CG2
- | CG4
- | CGOddPrimePower (Prime a) Word
- | CGDoubleOddPrimePower (Prime a) Word
- cyclicGroupFromModulo :: (Ord a, Integral a, UniqueFactorisation a) => a -> Maybe (CyclicGroup a)
- cyclicGroupToModulo :: Euclidean a => CyclicGroup a -> Prefactored a
- groupSize :: (Euclidean a, UniqueFactorisation a) => CyclicGroup a -> Prefactored a
- data PrimitiveRoot m
- unPrimitiveRoot :: PrimitiveRoot m -> MultMod m
- getGroup :: PrimitiveRoot m -> CyclicGroup Natural
- isPrimitiveRoot :: KnownNat n => Mod n -> Maybe (PrimitiveRoot n)
- isPrimitiveRoot' :: (Integral a, UniqueFactorisation a) => CyclicGroup a -> a -> Bool
Cyclic groups
data CyclicGroup a Source #
A multiplicative group of residues is called cyclic,
if there is a primitive root g,
whose powers generates all elements.
Any cyclic multiplicative group of residues
falls into one of the following cases.
Constructors
| CG2 | Residues modulo 2. |
| CG4 | Residues modulo 4. |
| CGOddPrimePower (Prime a) Word | Residues modulo |
| CGDoubleOddPrimePower (Prime a) Word | Residues modulo 2 |
Instances
cyclicGroupFromModulo :: (Ord a, Integral a, UniqueFactorisation a) => a -> Maybe (CyclicGroup a) Source #
Check whether a multiplicative group of residues, characterized by its modulo, is cyclic and, if yes, return its form.
>>>cyclicGroupFromModulo 4Just CG4>>>cyclicGroupFromModulo (2 * 13 ^ 3)Just (CGDoubleOddPrimePower (Prime 13) 3)>>>cyclicGroupFromModulo (4 * 13)Nothing
cyclicGroupToModulo :: Euclidean a => CyclicGroup a -> Prefactored a Source #
Extract modulo and its factorisation from a cyclic multiplicative group of residues.
>>>cyclicGroupToModulo CG4Prefactored {prefValue = 4, prefFactors = Coprimes {unCoprimes = [(2,2)]}}
>>>import Data.Maybe>>>cyclicGroupToModulo (CGDoubleOddPrimePower (fromJust (isPrime 13)) 3)Prefactored {prefValue = 4394, prefFactors = Coprimes {unCoprimes = [(13,3),(2,1)]}}
groupSize :: (Euclidean a, UniqueFactorisation a) => CyclicGroup a -> Prefactored a Source #
Calculate the size of a given cyclic group.
Primitive roots
data PrimitiveRoot m Source #
PrimitiveRoot m is a type which is only inhabited
by primitive roots of m.
Instances
| Eq (PrimitiveRoot m) Source # | |
Defined in Math.NumberTheory.Moduli.PrimitiveRoot Methods (==) :: PrimitiveRoot m -> PrimitiveRoot m -> Bool # (/=) :: PrimitiveRoot m -> PrimitiveRoot m -> Bool # | |
| KnownNat m => Show (PrimitiveRoot m) Source # | |
Defined in Math.NumberTheory.Moduli.PrimitiveRoot Methods showsPrec :: Int -> PrimitiveRoot m -> ShowS # show :: PrimitiveRoot m -> String # showList :: [PrimitiveRoot m] -> ShowS # | |
unPrimitiveRoot :: PrimitiveRoot m -> MultMod m Source #
Extract primitive root value.
getGroup :: PrimitiveRoot m -> CyclicGroup Natural Source #
Get cyclic group structure.
isPrimitiveRoot :: KnownNat n => Mod n -> Maybe (PrimitiveRoot n) Source #
Check whether a given modular residue is a primitive root.
>>>:set -XDataKinds>>>isPrimitiveRoot (1 :: Mod 13)Nothing>>>isPrimitiveRoot (2 :: Mod 13)Just (PrimitiveRoot {unPrimitiveRoot = MultMod {multElement = (2 `modulo` 13)}, getGroup = CGOddPrimePower (Prime 13) 1})
This function is a convenient wrapper around isPrimitiveRoot'. The latter
provides better control and performance, if you need them.
isPrimitiveRoot' :: (Integral a, UniqueFactorisation a) => CyclicGroup a -> a -> Bool Source #
isPrimitiveRoot' cg a checks whether a is
a primitive root
of a given cyclic multiplicative group of residues cg.
>>>let Just cg = cyclicGroupFromModulo 13>>>isPrimitiveRoot' cg 1False>>>isPrimitiveRoot' cg 2True