Skip to content

Commit 0ae09c1

Browse files
committed
ormolu
1 parent b6cdc46 commit 0ae09c1

18 files changed

+498
-434
lines changed

bench/Bench/Binary.hs

+2-4
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,10 @@
11
module Bench.Binary where
22

3-
import Protolude
4-
3+
import Bench.Galois
54
import Control.Monad.Random
65
import Criterion.Main
76
import Data.Field.Galois
8-
9-
import Bench.Galois
7+
import Protolude
108

119
type F2m = Binary 0x80000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000425
1210

bench/Bench/Extension.hs

+9-5
Original file line numberDiff line numberDiff line change
@@ -1,27 +1,31 @@
11
module Bench.Extension where
22

3-
import Protolude
4-
3+
import Bench.Galois
4+
import Bench.Prime
55
import Control.Monad.Random
66
import Criterion.Main
77
import Data.Field.Galois
8-
9-
import Bench.Galois
10-
import Bench.Prime
8+
import Protolude
119

1210
data PU
11+
1312
instance IrreducibleMonic PU Fq where
1413
poly _ = X2 + 1
14+
1515
type Fq2 = Extension PU Fq
1616

1717
data PV
18+
1819
instance IrreducibleMonic PV Fq2 where
1920
poly _ = X3 - 9 - Y X
21+
2022
type Fq6 = Extension PV Fq2
2123

2224
data PW
25+
2326
instance IrreducibleMonic PW Fq6 where
2427
poly _ = X2 - Y X
28+
2529
type Fq12 = Extension PW Fq6
2630

2731
fq12 :: Fq12

bench/Bench/Galois.hs

+22-21
Original file line numberDiff line numberDiff line change
@@ -1,27 +1,28 @@
11
module Bench.Galois where
22

3-
import Protolude
4-
53
import Criterion.Main
64
import Data.Field.Galois
75
import GHC.Base
6+
import Protolude
87

9-
benchmark :: GaloisField k => String -> k -> k -> Benchmark
10-
benchmark s a b = bgroup s
11-
[ bench "Addition" $
12-
nf (uncurry (+)) (a, b)
13-
, bench "Multiplication" $
14-
nf (uncurry (*)) (a, b)
15-
, bench "Negation" $
16-
nf negate a
17-
, bench "Subtraction" $
18-
nf (uncurry (-)) (a, b)
19-
, bench "Inversion" $
20-
nf recip a
21-
, bench "Division" $
22-
nf (uncurry (/)) (a, b)
23-
, bench "Frobenius endomorphism" $
24-
nf frob a
25-
, bench "Square root" $
26-
nf sr a
27-
]
8+
benchmark :: (GaloisField k) => String -> k -> k -> Benchmark
9+
benchmark s a b =
10+
bgroup
11+
s
12+
[ bench "Addition" $
13+
nf (uncurry (+)) (a, b),
14+
bench "Multiplication" $
15+
nf (uncurry (*)) (a, b),
16+
bench "Negation" $
17+
nf negate a,
18+
bench "Subtraction" $
19+
nf (uncurry (-)) (a, b),
20+
bench "Inversion" $
21+
nf recip a,
22+
bench "Division" $
23+
nf (uncurry (/)) (a, b),
24+
bench "Frobenius endomorphism" $
25+
nf frob a,
26+
bench "Square root" $
27+
nf sr a
28+
]

bench/Bench/Prime.hs

+2-4
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,10 @@
11
module Bench.Prime where
22

3-
import Protolude
4-
3+
import Bench.Galois
54
import Control.Monad.Random
65
import Criterion.Main
76
import Data.Field.Galois
8-
9-
import Bench.Galois
7+
import Protolude
108

119
type Fq = Prime 21888242871839275222246405745257275088696311157297823662689037894645226208583
1210

bench/Main.hs

+5-6
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,12 @@
11
module Main where
22

3-
import Protolude
4-
5-
import Criterion.Main
6-
73
import Bench.Binary
84
import Bench.Extension
95
import Bench.Prime
6+
import Criterion.Main
7+
import Protolude
108

119
main :: IO ()
12-
main = defaultMain
13-
[benchBinary, benchExtension, benchPrime]
10+
main =
11+
defaultMain
12+
[benchBinary, benchExtension, benchPrime]

src/Data/Field/Galois/Base.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ where
55

66
import Control.Monad.Random (Random)
77
import Data.Field (Field)
8-
import qualified Data.Group as G (Group (..))
8+
import Data.Group qualified as G (Group (..))
99
import GHC.Natural (Natural)
1010
import Protolude hiding (one, quot, (-))
1111
import Test.QuickCheck (Arbitrary)

0 commit comments

Comments
 (0)