Skip to content

Commit

Permalink
[Bodigrim#118] Add Eisenstein integer benchmark module
Browse files Browse the repository at this point in the history
  • Loading branch information
rockbmb committed Aug 25, 2018
1 parent 9877dc0 commit 7996d9a
Show file tree
Hide file tree
Showing 5 changed files with 42 additions and 1 deletion.
12 changes: 12 additions & 0 deletions Math/NumberTheory/UniqueFactorisation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ import Data.Coerce
import qualified Math.NumberTheory.Primes.Factorisation as F (factorise)
import Math.NumberTheory.Primes.Testing.Probabilistic as T (isPrime)
import Math.NumberTheory.Primes.Types (Prime, Prm(..), PrimeNat(..))
import qualified Math.NumberTheory.EisensteinIntegers as E
import qualified Math.NumberTheory.GaussianIntegers as G
import Math.NumberTheory.Utils.FromIntegral

Expand Down Expand Up @@ -76,3 +77,14 @@ instance UniqueFactorisation G.GaussianInteger where

factorise 0 = []
factorise g = map (coerce *** intToWord) $ G.factorise g

newtype EisensteinPrime = EisensteinPrime { _unEisensteinPrime :: E.EisensteinInteger }
deriving (Eq, Show)

type instance Prime E.EisensteinInteger = EisensteinPrime

instance UniqueFactorisation E.EisensteinInteger where
unPrime = coerce

factorise 0 = []
factorise e = map (coerce *** intToWord) $ E.factorise e
1 change: 1 addition & 0 deletions arithmoi.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -191,6 +191,7 @@ benchmark criterion
semigroups >=0.8
other-modules:
Math.NumberTheory.ArithmeticFunctionsBench
Math.NumberTheory.EisensteinIntegersBench
Math.NumberTheory.GaussianIntegersBench
Math.NumberTheory.GCDBench
Math.NumberTheory.JacobiBench
Expand Down
2 changes: 2 additions & 0 deletions benchmark/Bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module Main where
import Gauge.Main

import Math.NumberTheory.ArithmeticFunctionsBench as ArithmeticFunctions
import Math.NumberTheory.EisensteinIntegersBench as Eisenstein
import Math.NumberTheory.GaussianIntegersBench as Gaussian
import Math.NumberTheory.GCDBench as GCD
import Math.NumberTheory.JacobiBench as Jacobi
Expand All @@ -15,6 +16,7 @@ import Math.NumberTheory.SmoothNumbersBench as SmoothNumbers

main = defaultMain
[ ArithmeticFunctions.benchSuite
, Eisenstein.benchSuite
, Gaussian.benchSuite
, GCD.benchSuite
, Jacobi.benchSuite
Expand Down
26 changes: 26 additions & 0 deletions benchmark/Math/NumberTheory/EisensteinIntegersBench.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Math.NumberTheory.EisensteinIntegersBench
( benchSuite
) where

import Control.DeepSeq
import Gauge.Main

import Math.NumberTheory.ArithmeticFunctions (tau)
import Math.NumberTheory.EisensteinIntegers

instance NFData EisensteinInteger

benchFindPrime :: Integer -> Benchmark
benchFindPrime n = bench (show n) $ nf findPrime n

benchTau :: Integer -> Benchmark
benchTau n = bench (show n) $ nf (\m -> sum [tau (x :+ y) | x <- [1..m], y <- [0..m]] :: Word) n

benchSuite :: Benchmark
benchSuite = bgroup "Eisenstein"
[ bgroup "findPrime" $ map benchFindPrime [1000003, 10000141, 100000039, 1000000021, 10000000033, 100000000003, 1000000000039, 10000000000051]
, bgroup "tau" $ map benchTau [10, 20, 40, 80]
]
2 changes: 1 addition & 1 deletion benchmark/Math/NumberTheory/GaussianIntegersBench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,6 @@ benchTau n = bench (show n) $ nf (\m -> sum [tau (x :+ y) | x <- [1..m], y <- [0

benchSuite :: Benchmark
benchSuite = bgroup "Gaussian"
[ bgroup "findPrime" $ map benchFindPrime [1000033, 10000121, 100000037, 1000000009, 10000000033, 100000000057, 1000000000061, 10000000000037]
[ bgroup "findPrime" $ map benchFindPrime [1000033, 10000121, 100000037, 1000000021, 10000000033, 100000000057, 1000000000061, 10000000000037]
, bgroup "tau" $ map benchTau [10, 20, 40, 80]
]

0 comments on commit 7996d9a

Please sign in to comment.