4

I'm trying to learn a bit of Haskell by writing a small set of functions for computations over finite (Galois) fields. Years ago I wrote the first version of a similar library for the computer algebra system GNU Maxima (see here) and I thought I'd try the same thing with Haskell.

However, I'm getting myself all muddled with data types. For a finite field, you need a base prime q (the characteristic of the field), and a polynomial p(x) which is irreducible modulo q. If p(x) has degree n, then the order of the field is q^n and its elements are all polynomials (modulo q) with degree n-1 or less.

We can represent polynomials as lists of their coefficients, so that elements of the field are simply lists (or vectors, if you prefer) of elements of Z_q and of length n. Addition is done component-wise modulo q, and multiplication is done modulo p(x).

I reckon if I can get the data type and addition sorted out the rest will be straightforward. My first attempt is this:

import Data.List

data GF = GF {characteristic::Int
             ,power::Int
             ,poly::[Int]
             ,irreducible::[Int]
             } deriving(Eq, Show)

The power element is unnecessary - it is after all simply one less than the length of the irreducible polynomial - but it's a convenience to have it rather than having to compute it.

Then I had my addition function as:

addGF :: GF -> GF -> GF
addGF x y = GF q n zp p
  where
    q = characteristic x
    n = power x
    zp = zipWith (\i j -> rem (i+j) q) xp yp
      where
        xp = poly x
        yp = poly y
    p = irreducible x

This works, but is inelegant, and I'm sure very "un-Haskell-ish". Part of the problem is that I don't know how to decouple the definition (or type) of a Galois field from its elements.

What I need to do is to provide a general type for a field, and on top of that define elements of it. There are, after all, things I might want to do with a field which are independent of its elements, such as generate a normal basis, find a primitive element, generate a table of logarithms for a primitive element, generate random elements, etc.

So I guess my question is: how do I define a generic type of a Galois field, in such a way that operations on its elements are as natural as possible?

I have read a number of pages about defining data types, classes, etc, and I've no doubt that one of them contains the solution to my problem. But the more I read the more confused I become. All I want is for somebody to point me gently but firmly in the right direction. Thanks!

Alasdair
  • 1,300
  • 4
  • 16
  • 28
  • 2
    Not knowing anything about the domain, it looks like `poly` is what defines an "element", while the other three fields of `GF` characterize the "Galois field" per se, is that right? And so it would be an error if those three fields were not consistent between the two arguments of `addGF`? If that's right then the traditional approach would be to e.g. make `addGF :: GF -> GF -> Maybe GF` and return `Nothing` if the elements can't be added. If the parameters of the field are always expected to be known at compile time then you have various better options. – jberryman Jan 02 '18 at 04:17
  • I suspect your question is more or less the same as "what's a good API for vectors", which is pretty well-trodden territory. – jberryman Jan 02 '18 at 04:20
  • Helper functions for modular arithmetic could come in very handy: for example, if you’re computing a large expression such as a fold, it could defer the expensive `mod`/`rem` operation until the end, rather than doing it at every step. – Davislor Jan 02 '18 at 05:07
  • You also probably want to be able to write slices, such as `GF 7`, that you can then use with different characteristic polynomials. – Davislor Jan 02 '18 at 05:09
  • Depending on your operations, lists might have decent performance if you always walk them from front to back. Otherwise, you might find it better to store arrays. For some algorithms, it’s an advantage to use nested form for polynomials, but perhaps not this one? – Davislor Jan 02 '18 at 05:12
  • Thanks everyone. Yes, jberryman you are correct: the "poly" defines the element. And I take your point about Maybe, as you can't add elements from different fields. However, I was intending to leave that until I'd got the basic system sorted out. Note that I am very much a Haskell beginner - up to about the level of maps and folds (which I've used in other systems), but not Monads. I will also check out vectors (which maybe I should have done before posting). – Alasdair Jan 02 '18 at 05:53
  • That’s not a bad implementation of addition at all. Adding the check for the powers would be a simple matter of a pattern guard at the top of the function. – Davislor Jan 02 '18 at 06:24
  • I've tried `addGF :: GF -> GF -> Maybe GF` to get the error message `Couldn't match expected type ‘Maybe GF’ with actual type ‘GF’ `. There's a subtlety here which has confused me... – Alasdair Jan 02 '18 at 12:48

2 Answers2

2

I don't think your GF type is ugly or incorrect. The main issue I see is that addGF does not enforce that the elements can actually be added. Instead you could do:

addGF :: GF -> GF -> Maybe GF
addGF x y -- the pipes below are called "guards", a multi-way `if` syntax
  | q == characteristic y && n == power y && p == irreducible y = Just $ GF q n zp p
  | otherwise = Nothing
  where
    q = characteristic x
    n = power x
    zp = zipWith (\i j -> rem (i+j) q) xp yp
      where
        xp = poly x
        yp = poly y
    p = irreducible x

It might be more ergonomic and useful (but not a fundamentally different solution) to separate the notion of a field from its elements, like this:

-- these names are probably not appropriate
data Field  
  = Field { characteristic::Int
          , power::Int
          , irreducible::[Int]
          } deriving(Eq, Show)

-- formerly `GF`:
data FieldElement
  = FieldElement 
          { field::Field
          , poly::[Int]
          } deriving(Eq, Show)

Then in the guard above, you'd simply need to do e.g.

...
| field x == field y = Just $ ...

RecordWildCards is also a nice extension for removing boilerplate when you wish to work with record names.

If you know that you will be working with particular fields with parameters known at compile-time, then you can allow the type-checker to enforce the invariant in addGF for you. One way would be like this:

-- see `Data.Proxy` for info about this idiom
class SomeField f where
   characteristic :: proxy f -> Int
   power :: proxy f -> Int
   irreducible :: proxy f -> [Int]

-- A field element is just the polynomial, tagged with its field using the `f` type parameter
-- you may want to not expose the internals of `GF` but instead expose a 
-- makeGF function which enforces whatever invariants should hold between the parameters
-- of a field and the polynomial of its element.
newtype GF f = GF { poly :: [Int] }

-- `addGF` is no longer partial; the type system enforces that both arguments are elements of the same field
addGF :: (SomeField f)=> GF f -> GF f -> GF f
addGF x@(GF xp) (GF yp) = GF $ zipWith (\i j -> rem (i+j) q) xp yp
  where q = characteristic x

I mentioned "vectors" only be cause the problem and various approaches you have open to you here is the same as the one you have with vector arithmetic, in which e.g. only vectors of the same dimension can be added.

jberryman
  • 16,334
  • 5
  • 42
  • 83
  • Many thanks indeed for your detailed solution and discussion! I had tried doing something similar; except I had a `sameField` function which meant I could replace the first guard with `sameField x y = GF q n zp p`. I'm still getting my head around `Maybe`: can I use a `Just` result as input to another function as though the `Just` wasn't there? – Alasdair Jan 02 '18 at 16:05
  • Like `addGF x $ addGF y z` ? All field operations need to return results which can be used in other results. – Alasdair Jan 02 '18 at 16:22
  • I was just thinking: another approach would be comparable to what is done in `zipWith (+) [2,3] [1,2,3]`: the larger list is simply truncated to be the size of the smaller list. Similarly `addGF x y` could be made total by truncating (or otherwise reducing) an element of a larger field to an element of a smaller field. – Alasdair Jan 02 '18 at 16:56
  • `Maybe` is just a normal data type like your `GF`, only with two data constructors (`Just` and `Nothing`). Try opening ghci and typing `:info Maybe`. If you want to inspect a value of type `Maybe GF` you will need to pattern-match on it (or use a helper function (which is implemented with pattern-matching) like `maybe`. In ghci try `:t maybe`) – jberryman Jan 02 '18 at 20:19
  • @Alasdair, we often use the `Functor`, `Applicative`, and `Monad` instances of `Maybe` (and other types) for plumbing things through. They often help limit the syntactic overhead of dealing with partial functions and such. That said, if combining two things is simply an error and should never be done, there's not much shame in just throwing an error. – dfeuer Jan 02 '18 at 22:46
  • I'm still confused with `Maybe` and `Just`, since I'd like `addGF` to be applicable to elements both of type `GF` and of type `Maybe GF`. What would be handy is a version of `Maybe` that returns simply `a` rather than `Just a`. Unless this is displaying my monumental ignorance of types... – Alasdair Jan 03 '18 at 00:30
  • @Alasdair I think if you're patient with the first couple chapters of a Haskell book these things will be clear – jberryman Jan 03 '18 at 05:12
2

It is easy enough to lift characteristic and power into the type system in modern Haskell (GHC>=7.8), that is,

{-# LANGUAGE TypeOperators, DataKinds #-}
{-# LANGUAGE FlexibleContexts, TypeFamilies, UndecidableInstances #-}
{-# LANGUAGE StandaloneDeriving #-}

and express that the coefficients of the polynomials come from the finite group whose size is the characteristic:

import GHC.TypeLits
import Data.Modular

data GF χ -- characteristic
        n -- power
   = GF { irreducible :: [ℤ/χ]
        , poly :: [ℤ/χ]
        }

This already gives you for free that any additions on polynomials will be modulo χ.

You could furthermore express that there are always n + 1 coefficients:

import qualified Data.Vector.Fixed as Fix
import qualified Data.Vector.Fixed.Boxed as Fix

data GF χ n
   = GF { irreducible :: Fix.Vec (n+1) (ℤ/χ)
        , poly :: Fix.Vec (n+1) (ℤ/χ)
        }
deriving instance (KnownNat χ, Fix.Arity (n+1)) => Show (GF χ n)

addGF :: (KnownNat χ, Fix.Arity (n+1))
           => GF χ n -> GF χ n -> GF χ n
addGF (GF irr xp) (GF irr' yp)
 | irr==irr'  = GF irr $ Fix.zipWith (+) xp yp
 | otherwise  = error "Cannot add elements of finite fields with different irreducible polynomials!"

main = print (GF irr (Fix.fromList [0,0,1]) `addGF` GF irr (Fix.fromList [0,1,1])
               :: GF 2 2)
 where irr = Fix.fromList [1,1,1]

Result:

GF {irreducible = fromList [1,1,1], poly = fromList [0,1,0]}

It's still ugly that we have to runtime-check the irreducible polynomial. While it would in principle be possible to lift that into the type level as well, I'm not sure if that would really work out very well; we're already pushing against the boundaries here of how well Haskell can be used as a dependently-typed language. Perhaps it would be enough to choose for every characteristic and power only once an irreducible polynomial that would always be used?

leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • `reflection` is another option for making sure the polynomials match. It's a bit on the conservative side, but you can work around that with a runtime check if necessary. In particular, you can produce a `Coercion` between two types when you've verified they have equal irreducible polynomials. – dfeuer Jan 02 '18 at 22:39
  • Dear @leftaroundabout, thank you very much! - lots of good advice and great ideas. As for checking irreducibility, there are several options: (1) no checking; leave it to the user, noting that using a non-irreducible polynomial will lead to errors (such as elements not having inverses), (2) download, or provide online access to, a library of known polynomials - since most finite fields are "small" this may work, with the proviso that polynomials not in this library devolve to option (1), and (3) code up a criterion such as given at https://maths-people.anu.edu.au/~brent/pd/ANZMC08t4.pdf – Alasdair Jan 03 '18 at 00:26
  • I've tried this approach, also with advice from jberryman, to try to define `data GF = GF {characteristic::Integer, power::Integer , irreducible::[Mod Integer characteristic]} deriving(Eq, Show)` except this causes an error, that `characteristic` is not in scope. How can I define a variable to be a list of type `Mod Integer p` where p is the characteristic of the field? – Alasdair Jan 04 '18 at 02:56
  • @Alasdair you can only do that when `characteristic` lives in the type level, as it does in my examples. (Haskell strongly separates type- and value-level variables, in particular you can never just use a value to influence what type another value should have. Although, [`reflection`](https://hackage.haskell.org/package/reflection-2.1.2/docs/Data-Reflection.html), as dfeuer mentions, actually manages to do this, through clever higher-rank polymorphism.) – leftaroundabout Jan 04 '18 at 10:58