Skip to content

Commit

Permalink
Do not export Math.NumberTheory.Moduli.Equations.solveLinear'
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Sep 16, 2018
1 parent 08f3f14 commit 473a5ef
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 5 deletions.
12 changes: 8 additions & 4 deletions Math/NumberTheory/Moduli/DiscreteLogarithm.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,21 +7,24 @@
-- Portability: Non-portable
--

{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}

module Math.NumberTheory.Moduli.DiscreteLogarithm
( discreteLogarithm
) where

import qualified Data.IntMap.Strict as M
import Data.Maybe (maybeToList)
import Data.Proxy
import Numeric.Natural (Natural)
import GHC.Integer.GMP.Internals (recipModInteger, powModInteger)
import GHC.TypeNats.Compat

import Math.NumberTheory.Moduli.Chinese (chineseRemainder2)
import Math.NumberTheory.Moduli.Class (KnownNat, MultMod(..), Mod, getVal)
import Math.NumberTheory.Moduli.Equations (solveLinear')
import Math.NumberTheory.Moduli.Equations (solveLinear)
import Math.NumberTheory.Moduli.PrimitiveRoot (PrimitiveRoot(..), CyclicGroup(..))
import Math.NumberTheory.Powers.Squares (integerSquareRoot)
import Math.NumberTheory.UniqueFactorisation (unPrime)
Expand Down Expand Up @@ -113,7 +116,8 @@ discreteLogarithmPrimePollard p a b =
begin t = go (step t) (step (step t))
check t = powModInteger a t p == b
go tort@(xi,ai,bi) hare@(x2i,a2i,b2i)
| xi == x2i, gcd (bi - b2i) n < sqrtN = solveLinear' n (bi - b2i) (ai - a2i)
| xi == x2i, gcd (bi - b2i) n < sqrtN = case someNatVal (fromInteger n) of
SomeNat (Proxy :: Proxy n) -> map getVal $ solveLinear (fromInteger (bi - b2i) :: Mod n) (fromInteger (ai - a2i))
| xi == x2i = []
| otherwise = go (step tort) (step (step hare))
runPollard = filter check . begin . initialise
1 change: 0 additions & 1 deletion Math/NumberTheory/Moduli/Equations.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@

module Math.NumberTheory.Moduli.Equations
( solveLinear
, solveLinear'
, solveQuadratic
) where

Expand Down

0 comments on commit 473a5ef

Please sign in to comment.