diff --git a/ChangeLog.md b/ChangeLog.md
index 820912a..af01577 100644
--- a/ChangeLog.md
+++ b/ChangeLog.md
@@ -1,18 +1,23 @@
# Change log for galois-field
+## 0.2.1
+* Add preliminary implementation of BinaryField.
+* Add `frob` function for GaloisField.
+* Add minor improvements to documentation.
+
## 0.2.0
-* Add `deg` for GaloisField
-* Add `order` for GaloisField
-* Add `pow` for GaloisField
-* Add `rnd` for GaloisField
+* Add `deg` function for GaloisField.
+* Add `order` function for GaloisField.
+* Add `pow` function for GaloisField.
+* Add `rnd` function for GaloisField.
## 0.1.1
* Add `Arbitrary` instances to PrimeField, PolynomialRing, and ExtensionField.
* Add `Bits` instances to PrimeField.
* Add `Pretty` instances to PrimeField, PolynomialRing, and ExtensionField.
-* Minor optimisations to multiplication and inversion with `INLINE`.
+* Add minor optimisations to multiplication and inversion with `INLINE`.
## 0.1.0
diff --git a/README.md b/README.md
index 9f07521..e81d07e 100644
--- a/README.md
+++ b/README.md
@@ -1,7 +1,7 @@
-
-
-
+
+
+
@@ -14,11 +14,11 @@ An efficient implementation of Galois fields used in cryptography research.
## Technical background
-A **Galois field** GF(pq), for prime p and positive q, is a *field* (GF(pq), +, \*, 0, 1) of finite *order*. Explicitly,
-- (GF(pq), +, 0) is an abelian group,
-- (GF(pq) \\ \{0\}, \*, 1) is an abelian group,
+A **Galois field** GF(p^q), for prime p and positive q, is a *field* (GF(p^q), +, \*, 0, 1) of finite *order*. Explicitly,
+- (GF(p^q), +, 0) is an abelian group,
+- (GF(p^q) \\ \{0\}, \*, 1) is an abelian group,
- \* is distributive over +, and
-- \#GF(pq) is finite.
+- \#GF(p^q) is finite.
### Prime fields
@@ -28,9 +28,9 @@ For example, GF(4) is a Galois field of characteristic 2 that is a two-dimension
### Extension fields
-Any Galois field has order a prime power pq for prime p and positive q, and there is a Galois field GF(pq) of any prime power order pq that is *unique up to non-unique isomorphism*. Any Galois field GF(pq) can be constructed as an **extension field** over a smaller Galois subfield GF(pr), through the identification GF(pq) = GF(pr)[X] / \ for an *irreducible monic splitting polynomial* f(X) of degree q - r + 1 in the *polynomial ring* GF(pr)[X].
+Any Galois field has order a prime power p^q for prime p and positive q, and there is a Galois field GF(p^q) of any prime power order p^q that is *unique up to non-unique isomorphism*. Any Galois field GF(p^q) can be constructed as an **extension field** over a smaller Galois subfield GF(p^r), through the identification GF(p^q) = GF(p^r)[X] / \ for an *irreducible monic splitting polynomial* f(X) of degree q - r + 1 in the *polynomial ring* GF(p^r)[X].
-For example, GF(4) has order 22 and can be constructed as an extension field GF(2)[X] / \ where f(X) = X2 + X + 1 is an irreducible monic splitting quadratic polynomial in GF(2)[X].
+For example, GF(4) has order 2^2 and can be constructed as an extension field GF(2)[X] / \ where f(X) = X^2 + X + 1 is an irreducible monic splitting quadratic polynomial in GF(2)[X].
## Example usage
diff --git a/benchmarks/Main.hs b/benchmarks/Main.hs
index 1a352e4..8cf25a4 100644
--- a/benchmarks/Main.hs
+++ b/benchmarks/Main.hs
@@ -16,7 +16,7 @@ fq' = 10757805228921058098980668000791497318123219899766237205512608761387909753
data Pu
instance IrreducibleMonic Fq Pu where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type Fq2 = ExtensionField Fq Pu
fq2 :: Fq2
@@ -33,7 +33,7 @@ fq2' = fromList
data Pv
instance IrreducibleMonic Fq2 Pv where
- split _ = x^3 - (9 + t x)
+ split _ = x ^ (3 :: Int) - (9 + t x)
type Fq6 = ExtensionField Fq2 Pv
fq6 :: Fq6
@@ -70,7 +70,7 @@ fq6' = fromList
data Pw
instance IrreducibleMonic Fq6 Pw where
- split _ = x^2 - t x
+ split _ = x ^ (2 :: Int) - t x
type Fq12 = ExtensionField Fq6 Pw
fq12 :: Fq12
diff --git a/package.yaml b/package.yaml
index 07cfebd..0c80ec8 100644
--- a/package.yaml
+++ b/package.yaml
@@ -1,7 +1,7 @@
name: galois-field
-version: 0.2.0
+version: 0.2.1
synopsis: Galois field library
-description: Galois field library for cryptography research
+description: An efficient implementation of Galois fields used in cryptography research
maintainer: Adjoint Inc (info@adjoint.io)
license: MIT
github: adjoint-io/galois-field
@@ -34,14 +34,16 @@ extra-source-files:
- README.md
- ChangeLog.md
+ghc-options:
+ - -O2
+ - -Wall
+
library:
exposed-modules:
+ - BinaryField
+ - ExtensionField
- GaloisField
- PrimeField
- - ExtensionField
- ghc-options:
- - -O2
- - -Wall
other-modules:
- PolynomialRing
source-dirs:
@@ -52,9 +54,6 @@ tests:
main: Main
dependencies:
- tasty
- - tasty-discover
- ghc-options:
- - -O2
source-dirs:
- tests
- src
@@ -64,8 +63,6 @@ benchmarks:
main: Main
dependencies:
- criterion
- ghc-options:
- - -O2
source-dirs:
- benchmarks
- src
diff --git a/src/BinaryField.hs b/src/BinaryField.hs
new file mode 100644
index 0000000..6ccdde3
--- /dev/null
+++ b/src/BinaryField.hs
@@ -0,0 +1,108 @@
+module BinaryField
+ ( BinaryField
+ ) where
+
+import Protolude
+
+import Control.Monad.Random (Random(..), getRandom)
+import Test.Tasty.QuickCheck (Arbitrary(..), choose)
+import Text.PrettyPrint.Leijen.Text (Pretty(..))
+
+import GaloisField (GaloisField(..))
+
+-- | Binary fields @GF(2^q)[X]/\@ for @q@ positive and
+-- @f(X)@ irreducible monic in @GF(2^q)[X]@ encoded as an integer.
+newtype BinaryField (ib :: Nat) = BF Integer
+ deriving (Eq, Generic, NFData, Show)
+
+-- Binary fields are arbitrary.
+instance KnownNat ib => Arbitrary (BinaryField ib) where
+ arbitrary = BF <$> choose (0, 2 ^ natVal (witness :: BinaryField ib) - 1)
+
+-- Binary fields are fields.
+instance KnownNat ib => Fractional (BinaryField ib) where
+ recip y@(BF x) = case inv (natVal y) x of
+ Just z -> BF z
+ _ -> panic "no multiplicative inverse."
+ {-# INLINE recip #-}
+ fromRational (x:%y) = fromInteger x / fromInteger y
+ {-# INLINABLE fromRational #-}
+
+-- Binary fields are Galois fields.
+instance KnownNat ib => GaloisField (BinaryField ib) where
+ char = const 2
+ {-# INLINE char #-}
+ deg = bin . natVal
+ {-# INLINE deg #-}
+ frob = flip pow 2
+ {-# INLINE frob #-}
+ pow = (^)
+ {-# INLINE pow #-}
+ rnd = getRandom
+ {-# INLINE rnd #-}
+
+-- Binary fields are fields.
+instance KnownNat ib => Num (BinaryField ib) where
+ BF x + BF y = BF (xor x y)
+ {-# INLINE (+) #-}
+ BF x * BF y = fromInteger (mul x y)
+ {-# INLINE (*) #-}
+ BF x - BF y = BF (xor x y)
+ {-# INLINE (-) #-}
+ negate = identity
+ {-# INLINE negate #-}
+ fromInteger = BF . red (natVal (witness :: BinaryField ib))
+ {-# INLINABLE fromInteger #-}
+ abs = panic "not implemented."
+ signum = panic "not implemented."
+
+-- Binary fields are pretty.
+instance KnownNat ib => Pretty (BinaryField ib) where
+ pretty (BF x) = pretty x
+
+-- Binary fields are random.
+instance KnownNat ib => Random (BinaryField ib) where
+ random = first BF . randomR (0, 2 ^ natVal (witness :: BinaryField ib) - 1)
+ randomR = panic "not implemented."
+
+-- Binary logarithm.
+bin :: Integer -> Int
+bin = logP 2
+ where
+ logP :: Integer -> Integer -> Int
+ logP p x = let l = 2 * logP (p * p) x
+ in if x < p then 0 else log' l (quot x (p ^ l))
+ where
+ log' :: Int -> Integer -> Int
+ log' q y = if y < p then q else log' (q + 1) (quot y p)
+{-# INLINE bin #-}
+
+-- Binary multiplication.
+mul :: Integer -> Integer -> Integer
+mul x y = mul' (bin y) (if testBit y 0 then x else 0)
+ where
+ mul' :: Int -> Integer -> Integer
+ mul' 0 n = n
+ mul' l n = mul' (l - 1) (if testBit y l then xor n (shift x l) else n)
+{-# INLINE mul #-}
+
+-- Binary reduction.
+red :: Integer -> Integer -> Integer
+red f = red'
+ where
+ red' :: Integer -> Integer
+ red' x = let n = bin x - bin f
+ in if n < 0 then x else red' (xor x (shift f n))
+{-# INLINE red #-}
+
+-- Binary inversion.
+inv :: Integer -> Integer -> Maybe Integer
+inv f x = case inv' 1 x 0 f of
+ (y, 1) -> Just y
+ _ -> Nothing
+ where
+ inv' :: Integer -> Integer -> Integer -> Integer -> (Integer, Integer)
+ inv' t r _ 0 = (t, r)
+ inv' t r t' r' = let q = max 0 (bin r - bin r')
+ in inv' t' r' (xor t (shift t' q)) (xor r (shift r' q))
+{-# INLINE inv #-}
diff --git a/src/ExtensionField.hs b/src/ExtensionField.hs
index 206e23c..a6a052c 100644
--- a/src/ExtensionField.hs
+++ b/src/ExtensionField.hs
@@ -10,57 +10,58 @@ module ExtensionField
import Protolude
import Control.Monad.Random (Random(..), getRandom)
-import Test.Tasty.QuickCheck (Arbitrary(..), choose, sized)
+import Test.Tasty.QuickCheck (Arbitrary(..), vector)
import Text.PrettyPrint.Leijen.Text (Pretty(..))
import GaloisField (GaloisField(..))
import PolynomialRing (Polynomial(..), cut, polyInv, polyMul, polyQR)
--- | Irreducible monic splitting polynomial of extension field
-class IrreducibleMonic k im where
- {-# MINIMAL split #-}
- split :: ExtensionField k im -> Polynomial k -- ^ Splitting polynomial
-
--- | Extension fields @GF(p^q)[X]/@ for @p@ prime, @q@ positive, and
--- @f(X)@ irreducible monic in @GF(p^q)[X]@
+-- | Extension fields @GF(p^q)[X]/\@ for @p@ prime, @q@ positive, and
+-- @f(X)@ irreducible monic in @GF(p^q)[X]@.
newtype ExtensionField k im = EF (Polynomial k)
deriving (Eq, Generic, NFData, Show)
--- | Extension fields are arbitrary
+-- | Irreducible monic splitting polynomial @f(X)@ of extension field.
+class IrreducibleMonic k im where
+ {-# MINIMAL split #-}
+ -- | Splitting polynomial @f(X)@.
+ split :: ExtensionField k im -> Polynomial k
+
+-- Extension fields are arbitrary.
instance (Arbitrary k, GaloisField k, IrreducibleMonic k im)
=> Arbitrary (ExtensionField k im) where
- arbitrary = fromList <$> sized (const poly)
+ arbitrary = fromList <$> vector (length xs - 1)
where
- poly = choose (1, length xs - 1) >>= mapM (const arbitrary) . enumFromTo 1
- where
- X xs = split (witness :: ExtensionField k im)
+ X xs = split (witness :: ExtensionField k im)
--- | Extension fields are fields
+-- Extension fields are fields.
instance (GaloisField k, IrreducibleMonic k im)
=> Fractional (ExtensionField k im) where
- recip (EF (X ys)) = case polyInv ys xs of
+ recip y@(EF (X ys)) = case polyInv ys xs of
Just zs -> EF (X zs)
_ -> panic "no multiplicative inverse."
where
- X xs = split (witness :: ExtensionField k im)
+ X xs = split y
{-# INLINE recip #-}
fromRational (y:%z) = fromInteger y / fromInteger z
{-# INLINABLE fromRational #-}
--- | Extension fields are Galois fields
+-- Extension fields are Galois fields.
instance (GaloisField k, IrreducibleMonic k im)
=> GaloisField (ExtensionField k im) where
char = const (char (witness :: k))
{-# INLINE char #-}
- deg = const (deg (witness :: k) * length xs - 1)
+ deg y = deg (witness :: k) * (length xs - 1)
where
- X xs = split (witness :: ExtensionField k im)
+ X xs = split y
{-# INLINE deg #-}
+ frob = pow <*> char
+ {-# INLINE frob #-}
pow y@(EF (X ys)) n
| n < 0 = pow (recip y) (-n)
| otherwise = EF (X (pow' [1] ys n))
where
- X xs = split (witness :: ExtensionField k im)
+ X xs = split y
mul = (.) (snd . flip polyQR xs) . polyMul
pow' ws zs m
| m == 0 = ws
@@ -71,30 +72,30 @@ instance (GaloisField k, IrreducibleMonic k im)
rnd = getRandom
{-# INLINE rnd #-}
--- | Extension fields are rings
+-- Extension fields are rings.
instance (GaloisField k, IrreducibleMonic k im)
=> Num (ExtensionField k im) where
- EF y + EF z = EF (y + z)
+ EF y + EF z = EF (y + z)
{-# INLINE (+) #-}
- EF (X ys) * EF (X zs) = EF (X (snd (polyQR (polyMul ys zs) xs)))
+ y@(EF (X ys)) * EF (X zs) = EF (X (snd (polyQR (polyMul ys zs) xs)))
where
- X xs = split (witness :: ExtensionField k im)
+ X xs = split y
{-# INLINE (*) #-}
- EF y - EF z = EF (y - z)
+ EF y - EF z = EF (y - z)
{-# INLINE (-) #-}
- negate (EF y) = EF (-y)
+ negate (EF y) = EF (-y)
{-# INLINE negate #-}
- fromInteger = EF . fromInteger
+ fromInteger = EF . fromInteger
{-# INLINABLE fromInteger #-}
- abs = panic "not implemented."
- signum = panic "not implemented."
+ abs = panic "not implemented."
+ signum = panic "not implemented."
--- | Extension fields are pretty
+-- Extension fields are pretty.
instance (GaloisField k, IrreducibleMonic k im)
=> Pretty (ExtensionField k im) where
pretty (EF y) = pretty y
--- | Extension fields are random
+-- Extension fields are random.
instance (GaloisField k, IrreducibleMonic k im)
=> Random (ExtensionField k im) where
random = first (EF . X . cut) . unfold (length xs - 1) []
@@ -104,12 +105,12 @@ instance (GaloisField k, IrreducibleMonic k im)
let (y, g') = random g in unfold (n - 1) (y : ys) g'
randomR = panic "not implemented."
--- | List from field
+-- | Convert from field element to list representation.
fromField :: ExtensionField k im -> [k]
fromField (EF (X xs)) = xs
{-# INLINABLE fromField #-}
--- | Field from list
+-- | Convert from list representation to field element.
fromList :: forall k im . (GaloisField k, IrreducibleMonic k im)
=> [k] -> ExtensionField k im
fromList = EF . X . snd . flip polyQR xs . cut
@@ -117,12 +118,12 @@ fromList = EF . X . snd . flip polyQR xs . cut
X xs = split (witness :: ExtensionField k im)
{-# INLINABLE fromList #-}
--- | Current indeterminate variable
-x :: GaloisField k => Polynomial k
-x = X [0, 1]
-{-# INLINE x #-}
-
--- | Descend variable tower
+-- | Descend tower of indeterminate variables.
t :: Polynomial k -> Polynomial (ExtensionField k im)
t = X . return . EF
{-# INLINE t #-}
+
+-- | Current indeterminate variable.
+x :: GaloisField k => Polynomial k
+x = X [0, 1]
+{-# INLINE x #-}
diff --git a/src/GaloisField.hs b/src/GaloisField.hs
index 9cf3188..5f20f5c 100644
--- a/src/GaloisField.hs
+++ b/src/GaloisField.hs
@@ -8,22 +8,31 @@ import Control.Monad.Random (MonadRandom, Random)
import Test.Tasty.QuickCheck (Arbitrary)
import Text.PrettyPrint.Leijen.Text (Pretty)
--- | Galois fields @GF(p^q)@ for @p@ prime and @q@ non-negative
+-- | Galois fields @GF(p^q)@ for @p@ prime and @q@ non-negative.
class (Arbitrary k, Eq k, Fractional k, Pretty k, Random k, Show k)
=> GaloisField k where
- {-# MINIMAL char, deg, pow, rnd #-}
+ {-# MINIMAL char, deg, frob, pow, rnd #-}
-- Characteristics
- char :: k -> Integer -- ^ Characteristic @q@ of field
- deg :: k -> Int -- ^ Degree @q@ of field
+ -- | Characteristic @p@ of field and order of prime subfield.
+ char :: k -> Integer
- order :: k -> Integer -- ^ Order @p^q@ of field
+ -- | Degree @q@ of field as extension field over prime subfield.
+ deg :: k -> Int
+
+ -- | Frobenius endomorphism @x->x^p@ of prime subfield.
+ frob :: k -> k
+
+ -- | Order @p^q@ of field.
+ order :: k -> Integer
order = (^) <$> char <*> deg
{-# INLINE order #-}
-- Functions
- pow :: k -> Integer -> k -- @x@ to the power of @y@
- -- Randomisation
- rnd :: MonadRandom m => m k -- ^ Random element of field
+ -- | Exponentiation @x@ to the power of @y@.
+ pow :: k -> Integer -> k
+
+ -- | Randomised element @x@ of field.
+ rnd :: MonadRandom m => m k
diff --git a/src/PrimeField.hs b/src/PrimeField.hs
index 38e2e2d..8ccc101 100644
--- a/src/PrimeField.hs
+++ b/src/PrimeField.hs
@@ -12,33 +12,35 @@ import Text.PrettyPrint.Leijen.Text (Pretty(..))
import GaloisField (GaloisField(..))
--- | Prime fields @GF(p)@ for @p@ prime
+-- | Prime fields @GF(p)@ for @p@ prime.
newtype PrimeField (p :: Nat) = PF Integer
deriving (Bits, Eq, Generic, NFData, Show)
--- | Prime fields are arbitrary
+-- Prime fields are arbitrary.
instance KnownNat p => Arbitrary (PrimeField p) where
arbitrary = fromInteger <$> arbitrary
--- | Prime fields are fields
+-- Prime fields are fields.
instance KnownNat p => Fractional (PrimeField p) where
recip y@(PF x) = PF (recipModInteger x (natVal y))
{-# INLINE recip #-}
fromRational (x:%y) = fromInteger x / fromInteger y
{-# INLINABLE fromRational #-}
--- | Prime fields are Galois fields
+-- Prime fields are Galois fields.
instance KnownNat p => GaloisField (PrimeField p) where
char = natVal
{-# INLINE char #-}
deg = const 1
{-# INLINE deg #-}
+ frob = identity
+ {-# INLINE frob #-}
pow y@(PF x) n = PF (powModInteger x n (natVal y))
{-# INLINE pow #-}
rnd = getRandom
{-# INLINE rnd #-}
--- | Prime fields are rings
+-- Prime fields are rings.
instance KnownNat p => Num (PrimeField p) where
z@(PF x) + PF y = PF (if xyp >= 0 then xyp else xy)
where
@@ -61,16 +63,16 @@ instance KnownNat p => Num (PrimeField p) where
abs = panic "not implemented."
signum = panic "not implemented."
--- | Prime fields are pretty
+-- Prime fields are pretty.
instance KnownNat p => Pretty (PrimeField p) where
pretty (PF x) = pretty [x]
--- | Prime fields are random
+-- Prime fields are random.
instance KnownNat p => Random (PrimeField p) where
random = first PF . randomR (0, natVal (witness :: PrimeField p) - 1)
randomR = panic "not implemented."
--- | Embed to integers
+-- | Embed field element to integers.
toInt :: PrimeField p -> Integer
toInt (PF x) = x
{-# INLINABLE toInt #-}
diff --git a/tests/ExtensionFieldTests.hs b/tests/ExtensionFieldTests.hs
index bb78cb1..6f34bfb 100644
--- a/tests/ExtensionFieldTests.hs
+++ b/tests/ExtensionFieldTests.hs
@@ -3,6 +3,7 @@ module ExtensionFieldTests where
import Protolude
import ExtensionField
+import PolynomialRing
import Test.Tasty
import GaloisFieldTests
@@ -10,111 +11,112 @@ import PrimeFieldTests
data P11
instance IrreducibleMonic FS2 P11 where
- split _ = x^2 + x + 1
+ split _ = x ^ (2 :: Int) + x + 1
type FS4 = ExtensionField FS2 P11
-test_S4 :: TestTree
-test_S4 = fieldAxioms (Proxy :: Proxy FS4) "FS4"
data P110
instance IrreducibleMonic FS2 P110 where
- split _ = x^3 + x + 1
+ split _ = x ^ (3 :: Int) + x + 1
type FS8 = ExtensionField FS2 P110
-test_S8 :: TestTree
-test_S8 = fieldAxioms (Proxy :: Proxy FS8) "FS8"
data P101
instance IrreducibleMonic FS2 P101 where
- split _ = x^3 + x^2 + 1
+ split _ = x ^ (3 :: Int) + x ^ (2 :: Int) + 1
type FS8' = ExtensionField FS2 P101
-test_S8' :: TestTree
-test_S8' = fieldAxioms (Proxy :: Proxy FS8') "FS8'"
data P10
instance IrreducibleMonic FS3 P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FS9 = ExtensionField FS3 P10
-test_S9 :: TestTree
-test_S9 = fieldAxioms (Proxy :: Proxy FS9) "FS9"
data P21
instance IrreducibleMonic FS3 P21 where
- split _ = x^2 + x - 1
+ split _ = x ^ (2 :: Int) + x - 1
type FS9' = ExtensionField FS3 P21
-test_S9' :: TestTree
-test_S9' = fieldAxioms (Proxy :: Proxy FS9') "FS9'"
data P22
instance IrreducibleMonic FS3 P22 where
- split _ = x^2 - x - 1
+ split _ = x ^ (2 :: Int) - x - 1
type FS9'' = ExtensionField FS3 P22
-test_S9'' :: TestTree
-test_S9'' = fieldAxioms (Proxy :: Proxy FS9'') "FS9''"
instance IrreducibleMonic FM0 P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FL0 = ExtensionField FM0 P10
-test_L0 :: TestTree
-test_L0 = fieldAxioms (Proxy :: Proxy FL0) "FL0"
instance IrreducibleMonic FM1 P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FL1 = ExtensionField FM1 P10
-test_L1 :: TestTree
-test_L1 = fieldAxioms (Proxy :: Proxy FL1) "FL1"
instance IrreducibleMonic FM2 P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FL2 = ExtensionField FM2 P10
-test_L2 :: TestTree
-test_L2 = fieldAxioms (Proxy :: Proxy FL2) "FL2"
instance IrreducibleMonic FM3 P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FL3 = ExtensionField FM3 P10
-test_L3 :: TestTree
-test_L3 = fieldAxioms (Proxy :: Proxy FL3) "FL3"
instance IrreducibleMonic FM4 P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FL4 = ExtensionField FM4 P10
-test_L4 :: TestTree
-test_L4 = fieldAxioms (Proxy :: Proxy FL4) "FL4"
instance IrreducibleMonic FVL P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FV2 = ExtensionField FVL P10
-test_V2 :: TestTree
-test_V2 = fieldAxioms (Proxy :: Proxy FV2) "FV2"
instance IrreducibleMonic FXL P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FX2 = ExtensionField FXL P10
-test_X2 :: TestTree
-test_X2 = fieldAxioms (Proxy :: Proxy FX2) "FX2"
instance IrreducibleMonic FZL P10 where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type FZ2 = ExtensionField FZL P10
-test_Z2 :: TestTree
-test_Z2 = fieldAxioms (Proxy :: Proxy FZ2) "FZ2"
data Pu
instance IrreducibleMonic Fq Pu where
- split _ = x^2 + 1
+ split _ = x ^ (2 :: Int) + 1
type Fq2 = ExtensionField Fq Pu
-test_Fq2 :: TestTree
-test_Fq2 = fieldAxioms (Proxy :: Proxy Fq2) "Fq2"
data Pv
instance IrreducibleMonic Fq2 Pv where
- split _ = x^3 - (9 + t x)
+ split _ = x ^ (3 :: Int) - (9 + t x)
type Fq6 = ExtensionField Fq2 Pv
-test_Fq6 :: TestTree
-test_Fq6 = fieldAxioms (Proxy :: Proxy Fq6) "Fq6"
data Pw
instance IrreducibleMonic Fq6 Pw where
- split _ = x^2 - t x
+ split _ = x ^ (2 :: Int) - t x
type Fq12 = ExtensionField Fq6 Pw
-test_Fq12 :: TestTree
-test_Fq12 = fieldAxioms (Proxy :: Proxy Fq12) "Fq12"
+
+testExtensionField :: TestTree
+testExtensionField = testGroup "Extension fields"
+ [ testGroup "Polynomial rings"
+ [ ringAxioms "FS2[X]" (witness :: Polynomial FS2)
+ , ringAxioms "FS3[X]" (witness :: Polynomial FS3)
+ , ringAxioms "FS5[X]" (witness :: Polynomial FS5)
+ , ringAxioms "FS7[X]" (witness :: Polynomial FS7)
+ , ringAxioms "FM0[X]" (witness :: Polynomial FM0)
+ , ringAxioms "FM1[X]" (witness :: Polynomial FM1)
+ , ringAxioms "FM2[X]" (witness :: Polynomial FM2)
+ , ringAxioms "FM3[X]" (witness :: Polynomial FM3)
+ , ringAxioms "FM4[X]" (witness :: Polynomial FM4)
+ , ringAxioms "FVL[X]" (witness :: Polynomial FVL)
+ , ringAxioms "FXL[X]" (witness :: Polynomial FXL)
+ , ringAxioms "FZL[X]" (witness :: Polynomial FZL)
+ ]
+ , fieldAxioms "FS4" (witness :: FS4 )
+ , fieldAxioms "FS8" (witness :: FS8 )
+ , fieldAxioms "FS8'" (witness :: FS8' )
+ , fieldAxioms "FS9" (witness :: FS9 )
+ , fieldAxioms "FS9'" (witness :: FS9' )
+ , fieldAxioms "FS9''" (witness :: FS9'')
+ , fieldAxioms "FL0" (witness :: FL0 )
+ , fieldAxioms "FL1" (witness :: FL1 )
+ , fieldAxioms "FL2" (witness :: FL2 )
+ , fieldAxioms "FL3" (witness :: FL3 )
+ , fieldAxioms "FL4" (witness :: FL4 )
+ , fieldAxioms "FV2" (witness :: FV2 )
+ , fieldAxioms "FX2" (witness :: FX2 )
+ , fieldAxioms "FZ2" (witness :: FZ2 )
+ , fieldAxioms "Fq2" (witness :: Fq2 )
+ , fieldAxioms "Fq6" (witness :: Fq6 )
+ , fieldAxioms "Fq12" (witness :: Fq12 )
+ ]
diff --git a/tests/GaloisFieldTests.hs b/tests/GaloisFieldTests.hs
index a0e3d16..be759f5 100644
--- a/tests/GaloisFieldTests.hs
+++ b/tests/GaloisFieldTests.hs
@@ -22,8 +22,8 @@ inverses :: Eq a => (a -> a -> a) -> (a -> a) -> a -> a -> Bool
inverses op inv e x = op x (inv x) == e && op (inv x) x == e
ringAxioms :: forall r . (Arbitrary r, Eq r, Num r, Show r)
- => Proxy r -> TestName -> TestTree
-ringAxioms _ str = testGroup ("Test ring axioms of " <> str)
+ => TestName -> r -> TestTree
+ringAxioms s _ = testGroup ("Ring axioms of " <> s)
[ testProperty "commutativity of addition"
$ commutativity ((+) :: r -> r -> r)
, testProperty "commutativity of multiplication"
@@ -43,9 +43,9 @@ ringAxioms _ str = testGroup ("Test ring axioms of " <> str)
]
fieldAxioms :: forall k . (Arbitrary k, Eq k, Fractional k, Show k)
- => Proxy k -> TestName -> TestTree
-fieldAxioms p str = testGroup ("Test field axioms of " <> str)
- [ ringAxioms p str
+ => TestName -> k -> TestTree
+fieldAxioms s k = testGroup ("Field axioms of " <> s)
+ [ ringAxioms s k
, testProperty "multiplicative inverses"
$ \n -> n /= 0 ==> inverses ((*) :: k -> k -> k) recip 1 n
]
diff --git a/tests/Main.hs b/tests/Main.hs
index 327adf4..287e76c 100644
--- a/tests/Main.hs
+++ b/tests/Main.hs
@@ -1 +1,11 @@
-{-# OPTIONS_GHC -F -pgmF tasty-discover -optF --tree-display #-}
+module Main where
+
+import Protolude
+
+import Test.Tasty
+
+import ExtensionFieldTests
+import PrimeFieldTests
+
+main :: IO ()
+main = defaultMain $ testGroup "Tests" [testPrimeField, testExtensionField]
diff --git a/tests/PolynomialRingTests.hs b/tests/PolynomialRingTests.hs
deleted file mode 100644
index eef65dd..0000000
--- a/tests/PolynomialRingTests.hs
+++ /dev/null
@@ -1,45 +0,0 @@
-module PolynomialRingTests where
-
-import Protolude
-
-import PolynomialRing
-import Test.Tasty
-
-import PrimeFieldTests
-import GaloisFieldTests
-
-test_S2X :: TestTree
-test_S2X = ringAxioms (Proxy :: Proxy (Polynomial FS2)) "FS2[X]"
-
-test_S3X :: TestTree
-test_S3X = ringAxioms (Proxy :: Proxy (Polynomial FS3)) "FS3[X]"
-
-test_S5X :: TestTree
-test_S5X = ringAxioms (Proxy :: Proxy (Polynomial FS5)) "FS5[X]"
-
-test_S7X :: TestTree
-test_S7X = ringAxioms (Proxy :: Proxy (Polynomial FS7)) "FS7[X]"
-
-test_M0X :: TestTree
-test_M0X = ringAxioms (Proxy :: Proxy (Polynomial FM0)) "FM0[X]"
-
-test_M1X :: TestTree
-test_M1X = ringAxioms (Proxy :: Proxy (Polynomial FM1)) "FM1[X]"
-
-test_M2X :: TestTree
-test_M2X = ringAxioms (Proxy :: Proxy (Polynomial FM2)) "FM2[X]"
-
-test_M3X :: TestTree
-test_M3X = ringAxioms (Proxy :: Proxy (Polynomial FM3)) "FM3[X]"
-
-test_M4X :: TestTree
-test_M4X = ringAxioms (Proxy :: Proxy (Polynomial FM4)) "FM4[X]"
-
-test_VLX :: TestTree
-test_VLX = ringAxioms (Proxy :: Proxy (Polynomial FVL)) "FVL[X]"
-
-test_XLX :: TestTree
-test_XLX = ringAxioms (Proxy :: Proxy (Polynomial FXL)) "FXL[X]"
-
-test_ZLX :: TestTree
-test_ZLX = ringAxioms (Proxy :: Proxy (Polynomial FZL)) "FZL[X]"
diff --git a/tests/PrimeFieldTests.hs b/tests/PrimeFieldTests.hs
index a29d801..892a516 100644
--- a/tests/PrimeFieldTests.hs
+++ b/tests/PrimeFieldTests.hs
@@ -24,39 +24,18 @@ type FZL = PrimeField 7416400626275308015247871419019374740599407810975190239058
type Fq = PrimeField 21888242871839275222246405745257275088696311157297823662689037894645226208583
-
-test_S2 :: TestTree
-test_S2 = fieldAxioms (Proxy :: Proxy FS2) "FS2"
-
-test_S3 :: TestTree
-test_S3 = fieldAxioms (Proxy :: Proxy FS3) "FS3"
-
-test_S5 :: TestTree
-test_S5 = fieldAxioms (Proxy :: Proxy FS5) "FS5"
-
-test_S7 :: TestTree
-test_S7 = fieldAxioms (Proxy :: Proxy FS7) "FS7"
-
-test_M0 :: TestTree
-test_M0 = fieldAxioms (Proxy :: Proxy FM0) "FM0"
-
-test_M1 :: TestTree
-test_M1 = fieldAxioms (Proxy :: Proxy FM1) "FM1"
-
-test_M2 :: TestTree
-test_M2 = fieldAxioms (Proxy :: Proxy FM2) "FM2"
-
-test_M3 :: TestTree
-test_M3 = fieldAxioms (Proxy :: Proxy FM3) "FM3"
-
-test_M4 :: TestTree
-test_M4 = fieldAxioms (Proxy :: Proxy FM4) "FM4"
-
-test_VL :: TestTree
-test_VL = fieldAxioms (Proxy :: Proxy FVL) "FVL"
-
-test_XL :: TestTree
-test_XL = fieldAxioms (Proxy :: Proxy FXL) "FXL"
-
-test_ZL :: TestTree
-test_ZL = fieldAxioms (Proxy :: Proxy FZL) "FZL"
+testPrimeField :: TestTree
+testPrimeField = testGroup "Prime fields"
+ [ fieldAxioms "FS2" (witness :: FS2)
+ , fieldAxioms "FS3" (witness :: FS3)
+ , fieldAxioms "FS5" (witness :: FS5)
+ , fieldAxioms "FS7" (witness :: FS7)
+ , fieldAxioms "FM0" (witness :: FM0)
+ , fieldAxioms "FM1" (witness :: FM1)
+ , fieldAxioms "FM2" (witness :: FM2)
+ , fieldAxioms "FM3" (witness :: FM3)
+ , fieldAxioms "FM4" (witness :: FM4)
+ , fieldAxioms "FVL" (witness :: FVL)
+ , fieldAxioms "FXL" (witness :: FXL)
+ , fieldAxioms "FZL" (witness :: FZL)
+ ]