finite-fields-0.1: Arithmetic in finite fields
Safe HaskellNone
LanguageHaskell2010

Math.FiniteField.GaloisField.Small

Description

Small Galois fields via a precomputed table of Conway polynomials.

This covers:

  • all fields with order <= 2^30
  • all fields with characteristic < 2^16 and order < 2^64 (?)
  • higher powers for very small prime characteristic
  • some more

To look up Conway polynomials, see the module Math.FiniteField.Conway.

Synopsis

Witness for the existence of the field

data WitnessGF (p :: Nat) (m :: Nat) where Source #

We need either a Conway polynomial, or in the m=1 case, a proof that p is prime

Constructors

WitnessFp :: IsSmallPrime p -> WitnessGF p 1 
WitnessFq :: HasConwayPoly p m -> WitnessGF p m 

Instances

Instances details
Show (WitnessGF p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

Methods

showsPrec :: Int -> WitnessGF p m -> ShowS #

show :: WitnessGF p m -> String #

showList :: [WitnessGF p m] -> ShowS #

data SomeWitnessGF Source #

Constructors

forall p m. SomeWitnessGF (WitnessGF p m) 

Instances

Instances details
Show SomeWitnessGF Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

mkGaloisField :: Int -> Int -> Maybe SomeWitnessGF Source #

Usage:

mkGaloisField p m

to construct the field with q = p^m elements

Implementation note: For m=1 we may do a primality test, which is very slow at the moment. You can use unsafeGaloisField below to avoid this.

unsafeGaloisField :: Int -> Int -> SomeWitnessGF Source #

In the case of m=1 you are responsible for guaranteeing that p is a prime (for m>1 we have to look up a Conway polynomial anyway).

Field elements

data GF (p :: Nat) (m :: Nat) Source #

An element of the Galois field of order q = p^m

Instances

Instances details
Eq (GF p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

Methods

(==) :: GF p m -> GF p m -> Bool #

(/=) :: GF p m -> GF p m -> Bool #

Fractional (GF p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

Methods

(/) :: GF p m -> GF p m -> GF p m #

recip :: GF p m -> GF p m #

fromRational :: Rational -> GF p m #

Num (GF p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

Methods

(+) :: GF p m -> GF p m -> GF p m #

(-) :: GF p m -> GF p m -> GF p m #

(*) :: GF p m -> GF p m -> GF p m #

negate :: GF p m -> GF p m #

abs :: GF p m -> GF p m #

signum :: GF p m -> GF p m #

fromInteger :: Integer -> GF p m #

Ord (GF p m) Source #

Note: the Ord instance is present only so that you can use GF as key in Maps - the ordering is kind of arbitrary!

Instance details

Defined in Math.FiniteField.GaloisField.Small

Methods

compare :: GF p m -> GF p m -> Ordering #

(<) :: GF p m -> GF p m -> Bool #

(<=) :: GF p m -> GF p m -> Bool #

(>) :: GF p m -> GF p m -> Bool #

(>=) :: GF p m -> GF p m -> Bool #

max :: GF p m -> GF p m -> GF p m #

min :: GF p m -> GF p m -> GF p m #

Show (GF p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

Methods

showsPrec :: Int -> GF p m -> ShowS #

show :: GF p m -> String #

showList :: [GF p m] -> ShowS #

Field (GF p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

Associated Types

type Witness (GF p m) = (r :: Type) Source #

Methods

characteristic :: Witness (GF p m) -> Integer Source #

dimension :: Witness (GF p m) -> Integer Source #

fieldSize :: Witness (GF p m) -> Integer Source #

zero :: Witness (GF p m) -> GF p m Source #

one :: Witness (GF p m) -> GF p m Source #

isZero :: GF p m -> Bool Source #

isOne :: GF p m -> Bool Source #

embed :: Witness (GF p m) -> Integer -> GF p m Source #

embedSmall :: Witness (GF p m) -> Int -> GF p m Source #

randomFieldElem :: RandomGen gen => Witness (GF p m) -> gen -> (GF p m, gen) Source #

randomInvertible :: RandomGen gen => Witness (GF p m) -> gen -> (GF p m, gen) Source #

primGen :: Witness (GF p m) -> GF p m Source #

witnessOf :: GF p m -> Witness (GF p m) Source #

power :: GF p m -> Integer -> GF p m Source #

powerSmall :: GF p m -> Int -> GF p m Source #

enumerate :: Witness (GF p m) -> [GF p m] Source #

type Witness (GF p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Small

type Witness (GF p m) = WitnessGF p m