Git Product home page Git Product logo

galois-field's Introduction

Galois Field

Hackage

An efficient implementation of Galois fields used in cryptography research.

Technical background

A Galois field , for prime and positive , is a field (, +, , 0, 1) of finite order. Explicitly,

  • (, +, 0) is an abelian group,
  • (, , 1) is an abelian group,
  • is distributive over +, and
  • is finite.

Prime fields

Any Galois field has a unique characteristic , the minimum positive such that , and is prime. The smallest Galois field of characteristic is a prime field, and any Galois field of characteristic is a finite-dimensional vector space over its prime subfield.

For example, is a Galois field of characteristic 2 that is a two-dimensional vector space over the prime subfield .

Extension fields

Any Galois field has order a prime power for prime and positive , and there is a Galois field of any prime power order that is unique up to non-unique isomorphism. Any Galois field can be constructed as an extension field over a smaller Galois subfield , through the identification for an irreducible monic polynomial of degree in the polynomial ring .

For example, has order and can be constructed as an extension field where is an irreducible monic quadratic polynomial in .

Binary fields

A Galois field of the form for big positive is a sum of for a non-empty set of . 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, can be represented as the integer 283 that represents the bit string 100011011.

Example usage

Include the following required language extensions.

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE PatternSynonyms #-}

Import the following functions at minimum.

import Data.Field.Galois (Prime, Extension, IrreducibleMonic(poly), Binary,
                          pattern X, pattern X2, pattern X3, pattern Y)

Prime fields

The following type declaration creates a prime field of a given characteristic.

type Fq = Prime 21888242871839275222246405745257275088696311157297823662689037894645226208583

Note that the characteristic given must be prime.

Galois field arithmetic can then be performed in this prime field.

fq :: Fq
fq = 5216004179354450092383934373463611881445186046129513844852096383579774061693

fq' :: Fq
fq' = 10757805228921058098980668000791497318123219899766237205512608761387909753942

arithmeticFq :: (Fq, Fq, Fq, Fq)
arithmeticFq = (fq + fq', fq - fq', fq * fq', fq / fq')

Extension fields

The following data type declaration creates a polynomial given an irreducible monic polynomial.

data P2
instance IrreducibleMonic P2 Fq where
  poly _ = X2 + 1

The following type declaration then creates an extension field with this polynomial.

type Fq2 = Extension P2 Fq

Note that the polynomial given must be irreducible and monic in the prime field.

Similarly, further extension fields can be constructed iteratively as follows.

data P6
instance IrreducibleMonic P6 Fq2 where
  poly _ = X3 - (9 + Y X)

type Fq6 = Extension P6 Fq2

data P12
instance IrreducibleMonic P12 Fq6 where
  poly _ = X2 - Y X

type Fq12 = Extension P12 Fq6

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.

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

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

arithmeticFq12 :: (Fq12, Fq12, Fq12, Fq12)
arithmeticFq12 = (fq12 + fq12', fq12 - fq12', fq12 * fq12', fq12 / fq12')

Note that

where , , is a tower of indeterminate variables, is constructed by

[ [ [a, b], [c, d], [e, f] ]
, [ [g, h], [i, j], [k, l] ] ] :: Fq12

Binary fields

The following type declaration creates a binary field modulo a given irreducible binary polynomial.

type F2m = Binary 0x80000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000425

Note that the polynomial given must be irreducible in .

Galois field arithmetic can then be performed in this binary field.

f2m :: F2m
f2m = 0x303001d34b856296c16c0d40d3cd7750a93d1d2955fa80aa5f40fc8db7b2abdbde53950f4c0d293cdd711a35b67fb1499ae60038614f1394abfa3b4c850d927e1e7769c8eec2d19

f2m' :: F2m
f2m' = 0x37bf27342da639b6dccfffeb73d69d78c6c27a6009cbbca1980f8533921e8a684423e43bab08a576291af8f461bb2a8b3531d2f0485c19b16e2f1516e23dd3c1a4827af1b8ac15b

arithmeticF2m :: (F2m, F2m, F2m, F2m)
arithmeticF2m = (f2m + f2m', f2m - f2m', f2m * f2m', f2m / f2m')

Disclaimer

This is experimental code meant for research-grade projects only. Please do not use this code in production until it has matured significantly.

License

Copyright (c) 2019-2024 Stephen Diehl.

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM,
DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR
OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE
OR OTHER DEALINGS IN THE SOFTWARE.

galois-field's People

Contributors

acentelles avatar bodigrim avatar sdiehl avatar sumo avatar texify[bot] avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

galois-field's Issues

Discussion: representation of polynomials

Stop me if I didn't get it right, but I understand that:

  • Elements of Galois fields on non-prime order are represented as polynomials over their prime field (modulo an irreducible polynomial, as it should)
  • Polynomials are represented as list of coefficients (specifically, [] is the 0 polynomial, and a:l is a+Xl)

I pretty much don't know anything about computer polynomial arithmetic. But I find it hard to imagine that this representation is the most efficient for the computations in this package. Maybe it is, but then this thread should gather evidence.

Fails to build with ghc 9.2 because of RULES recursion

Or at least that's why I assume happens. Here's the error message:

Simplifier ticks exhausted
  When trying RuleFired Extension.pow

And similar for Binary.pow

Upping the simplifier tick factor doesn't fix this, but removing the RULES entirely does.

Consider introduce fusion rules for prime fields

Taking the remainder is a potentially expensive computation.

So it may be worth it to consider adding fusion rules for consecutive arithmetic operations to eliminate intermediate remainder computations.

What should be the methods of the GaloisField class?

Currently, the GaloisField class has a single method: the characteristic (well, and arithmetic, of course).

This is definitely a bit weak, as there are infinite fields with finite characteristic.

So what other methods should there be?

One thing I've seen in the wild, is that people tend to tabulate their Galois field computation. So maybe there should be a method to do that? A witness of the group having finite order, rather than just finite characteristic?

Investigate slow inversion

Inversion and division operations in extension fields are currently slow due to a non-ideal implementation of polynomial division.

galois-field-0.4.1 fails to build with poly-0.3.2.0

I was able to reproduce this locally like so:

stack unpack galois-field-0.4.1 && cd galois-field-0.4.1
edit stack.yaml # add the following stack.yaml
stack build --test --bench --no-run-benchmarks --fast
# stack.yaml
resolver: nightly-2019-09-21
extra-deps:
- poly-0.3.2.0

The build errors being as follows:

[ 2 of 10] Compiling ExtensionField [Data.Poly.Semiring changed]

/Users/dan/scratch/galois-field-0.4.1/src/ExtensionField.hs:44:32: error:
    • Could not deduce (Data.Euclidean.Field k)
        arising from a use of ‘degree’
      from the context: IrreducibleMonic k im
        bound by the class declaration for ‘IrreducibleMonic’
        at src/ExtensionField.hs:38:24-39
      Possible fix:
        add (Data.Euclidean.Field k) to the context of
          the class declaration for ‘IrreducibleMonic’
    • In the first argument of ‘(.)’, namely ‘degree’
      In the second argument of ‘(.)’, namely ‘degree . split’
      In the second argument of ‘(.)’, namely
        ‘fromIntegral . degree . split’
   |
44 |   deg' = pred . fromIntegral . degree . split
   |                                ^^^^^^

/Users/dan/scratch/galois-field-0.4.1/src/ExtensionField.hs:75:23: error:
    • Could not deduce (Data.Euclidean.Field k)
        arising from a use of ‘rem’
      from the context: IrreducibleMonic k im
        bound by the instance declaration at src/ExtensionField.hs:72:10-59
      Possible fix:
        add (Data.Euclidean.Field k) to the context of
          the instance declaration
    • In the first argument of ‘EF’, namely
        ‘(rem (times x y) (split (witness :: ExtensionField k im)))’
      In the expression:
        EF (rem (times x y) (split (witness :: ExtensionField k im)))
      In an equation for ‘*’:
          EF x * EF y
            = EF (rem (times x y) (split (witness :: ExtensionField k im)))
   |
75 |   EF x * EF y   = EF (rem (times x y) (split (witness :: ExtensionField k im)))
   |                       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

/Users/dan/scratch/galois-field-0.4.1/src/ExtensionField.hs:159:21: error:
    • Could not deduce (Data.Euclidean.Field k)
        arising from a use of ‘rem’
      from the context: IrreducibleMonic k im
        bound by the type signature for:
                   toField :: forall k im.
                              IrreducibleMonic k im =>
                              [k] -> ExtensionField k im
        at src/ExtensionField.hs:158:1-76
      Possible fix:
        add (Data.Euclidean.Field k) to the context of
          the type signature for:
            toField :: forall k im.
                       IrreducibleMonic k im =>
                       [k] -> ExtensionField k im
    • In the first argument of ‘flip’, namely ‘rem’
      In the first argument of ‘(.)’, namely
        ‘flip rem (split (witness :: ExtensionField k im))’
      In the second argument of ‘(.)’, namely
        ‘flip rem (split (witness :: ExtensionField k im))
           . toPoly . fromList’
    |
159 | toField = EF . flip rem (split (witness :: ExtensionField k im)) . toPoly . fromList
    |                     ^^^

/Users/dan/scratch/galois-field-0.4.1/src/ExtensionField.hs:191:31: error:
    • Could not deduce (Data.Euclidean.Field k)
        arising from a use of ‘quot’
      from the context: GaloisField k
        bound by the type signature for:
                   polyGCD :: forall k.
                              GaloisField k =>
                              VPoly k -> VPoly k -> (VPoly k, VPoly k)
        at src/ExtensionField.hs:186:1-79
      Possible fix:
        add (Data.Euclidean.Field k) to the context of
          the type signature for:
            polyGCD :: forall k.
                       GaloisField k =>
                       VPoly k -> VPoly k -> (VPoly k, VPoly k)
    • In the expression: quot r r'
      In the expression:
        case quot r r' of {
          q -> polyGCD' s' (s - times q s') r' (r - times q r') }
      In an equation for ‘polyGCD'’:
          polyGCD' s s' r r'
            = case quot r r' of {
                q -> polyGCD' s' (s - times q s') r' (r - times q r') }
    |
191 |     polyGCD' s s' r r' = case quot r r' of
    |                               ^^^^^^^^^

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.