Skip to content

Commit

Permalink
Merge pull request #17 from adjoint-io/development
Browse files Browse the repository at this point in the history
Finalise 0.4 release
  • Loading branch information
sdiehl committed Aug 7, 2019
2 parents e17ee63 + 41e295d commit a2b9632
Show file tree
Hide file tree
Showing 16 changed files with 679 additions and 544 deletions.
11 changes: 11 additions & 0 deletions ChangeLog.md
@@ -1,5 +1,16 @@
# Change log for galois-field

## 0.4.0

* Add `Vector` implementation of extension fields.
* Add `qnr` function for Galois fields.
* Add `qr` function for Galois fields.
* Add `quad` function for extension fields and binary fields.
* Add `sr` function for extension fields and binary fields.
* Add `Semiring` instances for Galois fields.
* Add `Ord` instances for Galois fields.
* Add minor optimisations to exponentiation with `RULES`.

## 0.3.0

* Add complete implementation of binary fields.
Expand Down
59 changes: 31 additions & 28 deletions README.md
Expand Up @@ -33,7 +33,7 @@ For example, GF(4) has order 2^2 and can be constructed as an extension field GF

### Binary fields

A Galois field of the form GF(2^m) for big positive m is a sum of x^n for a non-empty set of 0 \< n \< m. For computational efficiency in cryptography, an element of a **binary field** can be represented by an integer that represents a bit string.
A Galois field of the form GF(2^m) for big positive m is a sum of X^n for a non-empty set of 0 \< n \< m. For computational efficiency in cryptography, an element of a **binary field** can be represented by an integer that represents a bit string. It should always be used when the field characteristic is 2.

For example, X^8 + X^4 + X^3 + X + 1 can be represented as the integer 283 that represents the bit string 100011011.

Expand All @@ -44,11 +44,14 @@ Include the following required language extensions.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
```
Import the following functions at minimum.
```haskell
import PrimeField (PrimeField)
import ExtensionField (ExtensionField, IrreducibleMonic(split), fromList, t, x)
import ExtensionField (ExtensionField, IrreducibleMonic(split), toField,
pattern X, pattern X2, pattern X3, pattern Y)
import BinaryField (BinaryField)
```

### Prime fields
Expand Down Expand Up @@ -77,7 +80,7 @@ The following data type declaration creates a splitting polynomial given an irre
```haskell
data P2
instance IrreducibleMonic Fq P2 where
split _ = x^2 + 1
split _ = X2 + 1
```
The following type declaration then creates an extension field with this splitting polynomial.
```haskell
Expand All @@ -89,78 +92,78 @@ Similarly, further extension fields can be constructed iteratively as follows.
```haskell
data P6
instance IrreducibleMonic Fq2 P6 where
split _ = x^3 - (9 + t x)
split _ = X3 - (9 + Y X)

type Fq6 = ExtensionField Fq2 P6

data P12
instance IrreducibleMonic Fq6 P12 where
split _ = x^2 - t x
split _ = X2 - Y X

type Fq12 = ExtensionField Fq6 P12
```
Note that `x` accesses the current indeterminate variable and `t` descends the tower of indeterminate variables.
Note that `X, X2, X3` accesses the current indeterminate variables and `Y` descends the tower of indeterminate variables.

Galois field arithmetic can then be performed in this extension field.
```haskell
fq12 :: Fq12
fq12 = fromList
[ fromList
[ fromList
fq12 = toField
[ toField
[ toField
[ 4025484419428246835913352650763180341703148406593523188761836807196412398582
, 5087667423921547416057913184603782240965080921431854177822601074227980319916
]
, fromList
, toField
[ 8868355606921194740459469119392835913522089996670570126495590065213716724895
, 12102922015173003259571598121107256676524158824223867520503152166796819430680
]
, fromList
, toField
[ 92336131326695228787620679552727214674825150151172467042221065081506740785
, 5482141053831906120660063289735740072497978400199436576451083698548025220729
]
]
, fromList
[ fromList
, toField
[ toField
[ 7642691434343136168639899684817459509291669149586986497725240920715691142493
, 1211355239100959901694672926661748059183573115580181831221700974591509515378
]
, fromList
, toField
[ 20725578899076721876257429467489710434807801418821512117896292558010284413176
, 17642016461759614884877567642064231230128683506116557502360384546280794322728
]
, fromList
, toField
[ 17449282511578147452934743657918270744212677919657988500433959352763226500950
, 1205855382909824928004884982625565310515751070464736233368671939944606335817
]
]
]

fq12' :: Fq12
fq12' = fromList
[ fromList
[ fromList
fq12' = toField
[ toField
[ toField
[ 495492586688946756331205475947141303903957329539236899715542920513774223311
, 9283314577619389303419433707421707208215462819919253486023883680690371740600
]
, fromList
, toField
[ 11142072730721162663710262820927009044232748085260948776285443777221023820448
, 1275691922864139043351956162286567343365697673070760209966772441869205291758
]
, fromList
, toField
[ 20007029371545157738471875537558122753684185825574273033359718514421878893242
, 9839139739201376418106411333971304469387172772449235880774992683057627654905
]
]
, fromList
[ fromList
, toField
[ toField
[ 9503058454919356208294350412959497499007919434690988218543143506584310390240
, 19236630380322614936323642336645412102299542253751028194541390082750834966816
]
, fromList
, toField
[ 18019769232924676175188431592335242333439728011993142930089933693043738917983
, 11549213142100201239212924317641009159759841794532519457441596987622070613872
]
, fromList
, toField
[ 9656683724785441232932664175488314398614795173462019188529258009817332577664
, 20666848762667934776817320505559846916719041700736383328805334359135638079015
]
Expand All @@ -172,12 +175,12 @@ arithmeticFq12 = (fq12 + fq12', fq12 - fq12', fq12 * fq12', fq12 / fq12')
```
Note that
```
a + bx + (c + dx)y + (e + fx)y^2 + (g + hx + (i + jx)y + (k + lx)y^2)z
a + bX + (c + dX)Y + (e + fX)Y^2 + (g + hX + (i + jX)Y + (k + lX)Y^2)Z
```
where `x, y, z` is a tower of indeterminate variables is constructed by
where `X, Y, Z` is a tower of indeterminate variables, is constructed by
```haskell
fromList [ fromList [fromList [a, b], fromList [c, d], fromList [e, f]]
, fromList [fromList [g, h], fromList [i, j], fromList [k, l]] ] :: Fq12
toField [ toField [toField [a, b], toField [c, d], toField [e, f]]
, toField [toField [g, h], toField [i, j], toField [k, l]] ] :: Fq12
```

### Binary fields
Expand Down
17 changes: 17 additions & 0 deletions benchmarks/BinaryFieldBenchmarks.hs
@@ -0,0 +1,17 @@
module BinaryFieldBenchmarks where

import BinaryField
import Criterion.Main

import GaloisFieldBenchmarks

type F2m = BinaryField 0x80000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000425

f2m :: F2m
f2m = 0x303001d34b856296c16c0d40d3cd7750a93d1d2955fa80aa5f40fc8db7b2abdbde53950f4c0d293cdd711a35b67fb1499ae60038614f1394abfa3b4c850d927e1e7769c8eec2d19

f2m' :: F2m
f2m' = 0x37bf27342da639b6dccfffeb73d69d78c6c27a6009cbbca1980f8533921e8a684423e43bab08a576291af8f461bb2a8b3531d2f0485c19b16e2f1516e23dd3c1a4827af1b8ac15b

benchmarkBinaryField :: Benchmark
benchmarkBinaryField = benchmark "BinaryField F2m" f2m f2m'
91 changes: 91 additions & 0 deletions benchmarks/ExtensionFieldBenchmarks.hs
@@ -0,0 +1,91 @@
module ExtensionFieldBenchmarks where

import Protolude

import Criterion.Main
import ExtensionField

import GaloisFieldBenchmarks
import PrimeFieldBenchmarks

data Pu
instance IrreducibleMonic Fq Pu where
split _ = X2 + 1
type Fq2 = ExtensionField Fq Pu

data Pv
instance IrreducibleMonic Fq2 Pv where
split _ = X3 - 9 - Y X
type Fq6 = ExtensionField Fq2 Pv

data Pw
instance IrreducibleMonic Fq6 Pw where
split _ = X2 - Y X
type Fq12 = ExtensionField Fq6 Pw

fq12 :: Fq12
fq12 = toField
[ toField
[ toField
[ 4025484419428246835913352650763180341703148406593523188761836807196412398582
, 5087667423921547416057913184603782240965080921431854177822601074227980319916
]
, toField
[ 8868355606921194740459469119392835913522089996670570126495590065213716724895
, 12102922015173003259571598121107256676524158824223867520503152166796819430680
]
, toField
[ 92336131326695228787620679552727214674825150151172467042221065081506740785
, 5482141053831906120660063289735740072497978400199436576451083698548025220729
]
]
, toField
[ toField
[ 7642691434343136168639899684817459509291669149586986497725240920715691142493
, 1211355239100959901694672926661748059183573115580181831221700974591509515378
]
, toField
[ 20725578899076721876257429467489710434807801418821512117896292558010284413176
, 17642016461759614884877567642064231230128683506116557502360384546280794322728
]
, toField
[ 17449282511578147452934743657918270744212677919657988500433959352763226500950
, 1205855382909824928004884982625565310515751070464736233368671939944606335817
]
]
]

fq12' :: Fq12
fq12' = toField
[ toField
[ toField
[ 495492586688946756331205475947141303903957329539236899715542920513774223311
, 9283314577619389303419433707421707208215462819919253486023883680690371740600
]
, toField
[ 11142072730721162663710262820927009044232748085260948776285443777221023820448
, 1275691922864139043351956162286567343365697673070760209966772441869205291758
]
, toField
[ 20007029371545157738471875537558122753684185825574273033359718514421878893242
, 9839139739201376418106411333971304469387172772449235880774992683057627654905
]
]
, toField
[ toField
[ 9503058454919356208294350412959497499007919434690988218543143506584310390240
, 19236630380322614936323642336645412102299542253751028194541390082750834966816
]
, toField
[ 18019769232924676175188431592335242333439728011993142930089933693043738917983
, 11549213142100201239212924317641009159759841794532519457441596987622070613872
]
, toField
[ 9656683724785441232932664175488314398614795173462019188529258009817332577664
, 20666848762667934776817320505559846916719041700736383328805334359135638079015
]
]
]

benchmarkExtensionField :: Benchmark
benchmarkExtensionField = benchmark "ExtensionField Fq12" fq12 fq12'
23 changes: 23 additions & 0 deletions benchmarks/GaloisFieldBenchmarks.hs
@@ -0,0 +1,23 @@
module GaloisFieldBenchmarks where

import Protolude

import Criterion.Main
import GaloisField
import GHC.Base

benchmark :: GaloisField k => String -> k -> k -> Benchmark
benchmark s a b = bgroup s
[ bench "Addition" $
whnf (uncurry (+)) (a, b)
, bench "Multiplication" $
whnf (uncurry (*)) (a, b)
, bench "Negation" $
whnf negate a
, bench "Subtraction" $
whnf (uncurry (-)) (a, b)
, bench "Inversion" $
whnf recip a
, bench "Division" $
whnf (uncurry (/)) (a, b)
]

0 comments on commit a2b9632

Please sign in to comment.