galois-field-1.0.0: Galois field library

Safe HaskellNone
LanguageHaskell2010

Data.Field.Galois

Contents

Synopsis

Documentation

module Data.Field

Galois fields

class (Arbitrary k, Field k, Fractional k, Generic k, Group k, NFData k, Ord k, Pretty k, Random k, Show k) => GaloisField k where Source #

Galois fields GF(p^q) for p prime and q non-negative.

Minimal complete definition

char, deg, frob

Methods

char :: k -> Natural Source #

Characteristic p of field and order of prime subfield.

deg :: k -> Word Source #

Degree q of field as extension field over prime subfield.

frob :: k -> k Source #

Frobenius endomorphism x -> x^p of prime subfield.

order :: k -> Natural Source #

Order p^q of field.

Instances
KnownNat p => GaloisField (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

KnownNat p => GaloisField (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

IrreducibleMonic p k => GaloisField (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

pow :: (GaloisField k, Integral n) => k -> n -> k Source #

Exponentiation of field element to integer.

Prime fields

data Prime (p :: Nat) Source #

Prime field elements.

Instances
KnownNat p => Bounded (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

minBound :: Prime p #

maxBound :: Prime p #

KnownNat p => Enum (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

succ :: Prime p -> Prime p #

pred :: Prime p -> Prime p #

toEnum :: Int -> Prime p #

fromEnum :: Prime p -> Int #

enumFrom :: Prime p -> [Prime p] #

enumFromThen :: Prime p -> Prime p -> [Prime p] #

enumFromTo :: Prime p -> Prime p -> [Prime p] #

enumFromThenTo :: Prime p -> Prime p -> Prime p -> [Prime p] #

Eq (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

(==) :: Prime p -> Prime p -> Bool #

(/=) :: Prime p -> Prime p -> Bool #

KnownNat p => Fractional (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

(/) :: Prime p -> Prime p -> Prime p #

recip :: Prime p -> Prime p #

fromRational :: Rational -> Prime p #

KnownNat p => Integral (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

quot :: Prime p -> Prime p -> Prime p #

rem :: Prime p -> Prime p -> Prime p #

div :: Prime p -> Prime p -> Prime p #

mod :: Prime p -> Prime p -> Prime p #

quotRem :: Prime p -> Prime p -> (Prime p, Prime p) #

divMod :: Prime p -> Prime p -> (Prime p, Prime p) #

toInteger :: Prime p -> Integer #

KnownNat p => Num (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

(+) :: Prime p -> Prime p -> Prime p #

(-) :: Prime p -> Prime p -> Prime p #

(*) :: Prime p -> Prime p -> Prime p #

negate :: Prime p -> Prime p #

abs :: Prime p -> Prime p #

signum :: Prime p -> Prime p #

fromInteger :: Integer -> Prime p #

Ord (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

compare :: Prime p -> Prime p -> Ordering #

(<) :: Prime p -> Prime p -> Bool #

(<=) :: Prime p -> Prime p -> Bool #

(>) :: Prime p -> Prime p -> Bool #

(>=) :: Prime p -> Prime p -> Bool #

max :: Prime p -> Prime p -> Prime p #

min :: Prime p -> Prime p -> Prime p #

KnownNat p => Real (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

toRational :: Prime p -> Rational #

Show (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

showsPrec :: Int -> Prime p -> ShowS #

show :: Prime p -> String #

showList :: [Prime p] -> ShowS #

Generic (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Associated Types

type Rep (Prime p) :: Type -> Type #

Methods

from :: Prime p -> Rep (Prime p) x #

to :: Rep (Prime p) x -> Prime p #

KnownNat p => Semigroup (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

(<>) :: Prime p -> Prime p -> Prime p #

sconcat :: NonEmpty (Prime p) -> Prime p #

stimes :: Integral b => b -> Prime p -> Prime p #

KnownNat p => Monoid (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

mempty :: Prime p #

mappend :: Prime p -> Prime p -> Prime p #

mconcat :: [Prime p] -> Prime p #

KnownNat p => Random (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

randomR :: RandomGen g => (Prime p, Prime p) -> g -> (Prime p, g) #

random :: RandomGen g => g -> (Prime p, g) #

randomRs :: RandomGen g => (Prime p, Prime p) -> g -> [Prime p] #

randoms :: RandomGen g => g -> [Prime p] #

randomRIO :: (Prime p, Prime p) -> IO (Prime p) #

randomIO :: IO (Prime p) #

KnownNat p => Arbitrary (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

arbitrary :: Gen (Prime p) #

shrink :: Prime p -> [Prime p] #

Bits (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

(.&.) :: Prime p -> Prime p -> Prime p #

(.|.) :: Prime p -> Prime p -> Prime p #

xor :: Prime p -> Prime p -> Prime p #

complement :: Prime p -> Prime p #

shift :: Prime p -> Int -> Prime p #

rotate :: Prime p -> Int -> Prime p #

zeroBits :: Prime p #

bit :: Int -> Prime p #

setBit :: Prime p -> Int -> Prime p #

clearBit :: Prime p -> Int -> Prime p #

complementBit :: Prime p -> Int -> Prime p #

testBit :: Prime p -> Int -> Bool #

bitSizeMaybe :: Prime p -> Maybe Int #

bitSize :: Prime p -> Int #

isSigned :: Prime p -> Bool #

shiftL :: Prime p -> Int -> Prime p #

unsafeShiftL :: Prime p -> Int -> Prime p #

shiftR :: Prime p -> Int -> Prime p #

unsafeShiftR :: Prime p -> Int -> Prime p #

rotateL :: Prime p -> Int -> Prime p #

rotateR :: Prime p -> Int -> Prime p #

popCount :: Prime p -> Int #

NFData (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

rnf :: Prime p -> () #

KnownNat p => Group (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

invert :: Prime p -> Prime p #

pow :: Integral x => Prime p -> x -> Prime p #

Hashable (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

hashWithSalt :: Int -> Prime p -> Int #

hash :: Prime p -> Int #

KnownNat p => GcdDomain (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

divide :: Prime p -> Prime p -> Maybe (Prime p) #

gcd :: Prime p -> Prime p -> Prime p #

lcm :: Prime p -> Prime p -> Prime p #

coprime :: Prime p -> Prime p -> Bool #

KnownNat p => Field (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

KnownNat p => Euclidean (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

quotRem :: Prime p -> Prime p -> (Prime p, Prime p) #

quot :: Prime p -> Prime p -> Prime p #

rem :: Prime p -> Prime p -> Prime p #

degree :: Prime p -> Natural #

KnownNat p => Semiring (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

plus :: Prime p -> Prime p -> Prime p #

zero :: Prime p #

times :: Prime p -> Prime p -> Prime p #

one :: Prime p #

fromNatural :: Natural -> Prime p #

KnownNat p => Ring (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

negate :: Prime p -> Prime p #

KnownNat p => Pretty (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

pretty :: Prime p -> Doc #

prettyList :: [Prime p] -> Doc #

KnownNat p => GaloisField (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

KnownNat p => PrimeField (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

fromP :: Prime p -> Integer Source #

KnownNat p => TowerOfFields (Prime p) (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Prime p -> Prime p Source #

KnownNat p => TowerOfFields (Prime 2) (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Prime 2 -> Binary p Source #

type Rep (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

type Rep (Prime p) = D1 (MetaData "Prime" "Data.Field.Galois.Prime" "galois-field-1.0.0-YpVwDeebGU1udy5ZORBqg" True) (C1 (MetaCons "P" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))

class GaloisField k => PrimeField k Source #

Prime fields GF(p) = Z/pZ for p prime.

Minimal complete definition

fromP

Instances
KnownNat p => PrimeField (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Prime

Methods

fromP :: Prime p -> Integer Source #

fromP :: PrimeField k => k -> Integer Source #

Convert from GF(p) to Z.

toP :: KnownNat p => Integer -> Prime p Source #

Safe convert from Z to GF(p).

toP' :: KnownNat p => Integer -> Prime p Source #

Unsafe convert from Z to GF(p).

Extension fields

data Extension p k Source #

Extension field elements.

Instances
(TowerOfFields k l, IrreducibleMonic p l, TowerOfFields l (Extension p l)) => TowerOfFields k (Extension p l) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: k -> Extension p l Source #

IrreducibleMonic p k => TowerOfFields k (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: k -> Extension p k Source #

IrreducibleMonic p k => IsList (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Associated Types

type Item (Extension p k) :: Type #

Methods

fromList :: [Item (Extension p k)] -> Extension p k #

fromListN :: Int -> [Item (Extension p k)] -> Extension p k #

toList :: Extension p k -> [Item (Extension p k)] #

Eq k => Eq (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

(==) :: Extension p k -> Extension p k -> Bool #

(/=) :: Extension p k -> Extension p k -> Bool #

IrreducibleMonic p k => Fractional (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

(/) :: Extension p k -> Extension p k -> Extension p k #

recip :: Extension p k -> Extension p k #

fromRational :: Rational -> Extension p k #

IrreducibleMonic p k => Num (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

(+) :: Extension p k -> Extension p k -> Extension p k #

(-) :: Extension p k -> Extension p k -> Extension p k #

(*) :: Extension p k -> Extension p k -> Extension p k #

negate :: Extension p k -> Extension p k #

abs :: Extension p k -> Extension p k #

signum :: Extension p k -> Extension p k #

fromInteger :: Integer -> Extension p k #

Ord k => Ord (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

compare :: Extension p k -> Extension p k -> Ordering #

(<) :: Extension p k -> Extension p k -> Bool #

(<=) :: Extension p k -> Extension p k -> Bool #

(>) :: Extension p k -> Extension p k -> Bool #

(>=) :: Extension p k -> Extension p k -> Bool #

max :: Extension p k -> Extension p k -> Extension p k #

min :: Extension p k -> Extension p k -> Extension p k #

Show k => Show (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

showsPrec :: Int -> Extension p k -> ShowS #

show :: Extension p k -> String #

showList :: [Extension p k] -> ShowS #

Generic (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Associated Types

type Rep (Extension p k) :: Type -> Type #

Methods

from :: Extension p k -> Rep (Extension p k) x #

to :: Rep (Extension p k) x -> Extension p k #

IrreducibleMonic p k => Semigroup (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

(<>) :: Extension p k -> Extension p k -> Extension p k #

sconcat :: NonEmpty (Extension p k) -> Extension p k #

stimes :: Integral b => b -> Extension p k -> Extension p k #

IrreducibleMonic p k => Monoid (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

mempty :: Extension p k #

mappend :: Extension p k -> Extension p k -> Extension p k #

mconcat :: [Extension p k] -> Extension p k #

IrreducibleMonic p k => Random (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

randomR :: RandomGen g => (Extension p k, Extension p k) -> g -> (Extension p k, g) #

random :: RandomGen g => g -> (Extension p k, g) #

randomRs :: RandomGen g => (Extension p k, Extension p k) -> g -> [Extension p k] #

randoms :: RandomGen g => g -> [Extension p k] #

randomRIO :: (Extension p k, Extension p k) -> IO (Extension p k) #

randomIO :: IO (Extension p k) #

IrreducibleMonic p k => Arbitrary (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

arbitrary :: Gen (Extension p k) #

shrink :: Extension p k -> [Extension p k] #

NFData k => NFData (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

rnf :: Extension p k -> () #

IrreducibleMonic p k => Group (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

invert :: Extension p k -> Extension p k #

pow :: Integral x => Extension p k -> x -> Extension p k #

IrreducibleMonic p k => GcdDomain (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

divide :: Extension p k -> Extension p k -> Maybe (Extension p k) #

gcd :: Extension p k -> Extension p k -> Extension p k #

lcm :: Extension p k -> Extension p k -> Extension p k #

coprime :: Extension p k -> Extension p k -> Bool #

IrreducibleMonic p k => Field (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

IrreducibleMonic p k => Euclidean (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

quotRem :: Extension p k -> Extension p k -> (Extension p k, Extension p k) #

quot :: Extension p k -> Extension p k -> Extension p k #

rem :: Extension p k -> Extension p k -> Extension p k #

degree :: Extension p k -> Natural #

IrreducibleMonic p k => Semiring (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

plus :: Extension p k -> Extension p k -> Extension p k #

zero :: Extension p k #

times :: Extension p k -> Extension p k -> Extension p k #

one :: Extension p k #

fromNatural :: Natural -> Extension p k #

IrreducibleMonic p k => Ring (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

negate :: Extension p k -> Extension p k #

IrreducibleMonic p k => Pretty (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

pretty :: Extension p k -> Doc #

prettyList :: [Extension p k] -> Doc #

IrreducibleMonic p k => GaloisField (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

IrreducibleMonic p k => ExtensionField (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

fromE :: (GaloisField l, IrreducibleMonic p0 l, Extension p k ~ Extension p0 l) => Extension p k -> [l] Source #

IrreducibleMonic p k => TowerOfFields (Extension p k) (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Extension p k -> Extension p k Source #

type Rep (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

type Rep (Extension p k) = D1 (MetaData "Extension" "Data.Field.Galois.Extension" "galois-field-1.0.0-YpVwDeebGU1udy5ZORBqg" True) (C1 (MetaCons "E" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (VPoly k))))
type Item (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

type Item (Extension p k) = k

class GaloisField k => ExtensionField k Source #

Extension fields GF(p^q)[X]/<f(X)> for p prime, q positive, and f(X) irreducible monic in GF(p^q)[X].

Minimal complete definition

fromE

Instances
IrreducibleMonic p k => ExtensionField (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Extension

Methods

fromE :: (GaloisField l, IrreducibleMonic p0 l, Extension p k ~ Extension p0 l) => Extension p k -> [l] Source #

class GaloisField k => IrreducibleMonic p k where Source #

Irreducible monic polynomial f(X) of extension field.

Methods

poly :: Extension p k -> VPoly k Source #

Polynomial f(X).

fromE :: (ExtensionField k, GaloisField l, IrreducibleMonic p l, k ~ Extension p l) => k -> [l] Source #

Convert from GF(p^q)[X]/<f(X)> to GF(p^q)[X].

conj :: IrreducibleMonic p k => Extension p k -> Extension p k Source #

Complex conjugation a+bi -> a-bi of quadratic extension field.

toE :: forall k p. IrreducibleMonic p k => [k] -> Extension p k Source #

Safe convert from GF(p^q)[X] to GF(p^q)[X]/<f(X)>.

toE' :: forall k p. IrreducibleMonic p k => [k] -> Extension p k Source #

Unsafe convert from GF(p^q)[X] to GF(p^q)[X]/<f(X)>.

pattern U :: IrreducibleMonic p k => Extension p k Source #

Pattern for field element U.

pattern U2 :: IrreducibleMonic p k => Extension p k Source #

Pattern for field element U^2.

pattern U3 :: IrreducibleMonic p k => Extension p k Source #

Pattern for field element U^3.

pattern V :: IrreducibleMonic p k => k -> Extension p k Source #

Pattern for descending tower of indeterminate variables for field elements.

pattern X :: GaloisField k => VPoly k Source #

Pattern for monic monomial X.

pattern X2 :: GaloisField k => VPoly k Source #

Pattern for monic monomial X^2.

pattern X3 :: GaloisField k => VPoly k Source #

Pattern for monic monomial X^3.

pattern Y :: IrreducibleMonic p k => VPoly k -> VPoly (Extension p k) Source #

Pattern for descending tower of indeterminate variables for monic monomials.

Binary fields

data Binary (p :: Nat) Source #

Binary field elements.

Instances
KnownNat p => IsList (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Associated Types

type Item (Binary p) :: Type #

Methods

fromList :: [Item (Binary p)] -> Binary p #

fromListN :: Int -> [Item (Binary p)] -> Binary p #

toList :: Binary p -> [Item (Binary p)] #

KnownNat p => Bounded (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

minBound :: Binary p #

maxBound :: Binary p #

KnownNat p => Enum (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

succ :: Binary p -> Binary p #

pred :: Binary p -> Binary p #

toEnum :: Int -> Binary p #

fromEnum :: Binary p -> Int #

enumFrom :: Binary p -> [Binary p] #

enumFromThen :: Binary p -> Binary p -> [Binary p] #

enumFromTo :: Binary p -> Binary p -> [Binary p] #

enumFromThenTo :: Binary p -> Binary p -> Binary p -> [Binary p] #

Eq (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

(==) :: Binary p -> Binary p -> Bool #

(/=) :: Binary p -> Binary p -> Bool #

KnownNat p => Fractional (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

(/) :: Binary p -> Binary p -> Binary p #

recip :: Binary p -> Binary p #

fromRational :: Rational -> Binary p #

KnownNat p => Integral (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

quot :: Binary p -> Binary p -> Binary p #

rem :: Binary p -> Binary p -> Binary p #

div :: Binary p -> Binary p -> Binary p #

mod :: Binary p -> Binary p -> Binary p #

quotRem :: Binary p -> Binary p -> (Binary p, Binary p) #

divMod :: Binary p -> Binary p -> (Binary p, Binary p) #

toInteger :: Binary p -> Integer #

KnownNat p => Num (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

(+) :: Binary p -> Binary p -> Binary p #

(-) :: Binary p -> Binary p -> Binary p #

(*) :: Binary p -> Binary p -> Binary p #

negate :: Binary p -> Binary p #

abs :: Binary p -> Binary p #

signum :: Binary p -> Binary p #

fromInteger :: Integer -> Binary p #

Ord (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

compare :: Binary p -> Binary p -> Ordering #

(<) :: Binary p -> Binary p -> Bool #

(<=) :: Binary p -> Binary p -> Bool #

(>) :: Binary p -> Binary p -> Bool #

(>=) :: Binary p -> Binary p -> Bool #

max :: Binary p -> Binary p -> Binary p #

min :: Binary p -> Binary p -> Binary p #

KnownNat p => Real (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

toRational :: Binary p -> Rational #

Show (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

showsPrec :: Int -> Binary p -> ShowS #

show :: Binary p -> String #

showList :: [Binary p] -> ShowS #

Generic (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Associated Types

type Rep (Binary p) :: Type -> Type #

Methods

from :: Binary p -> Rep (Binary p) x #

to :: Rep (Binary p) x -> Binary p #

KnownNat p => Semigroup (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

(<>) :: Binary p -> Binary p -> Binary p #

sconcat :: NonEmpty (Binary p) -> Binary p #

stimes :: Integral b => b -> Binary p -> Binary p #

KnownNat p => Monoid (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

mempty :: Binary p #

mappend :: Binary p -> Binary p -> Binary p #

mconcat :: [Binary p] -> Binary p #

KnownNat p => Random (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

randomR :: RandomGen g => (Binary p, Binary p) -> g -> (Binary p, g) #

random :: RandomGen g => g -> (Binary p, g) #

randomRs :: RandomGen g => (Binary p, Binary p) -> g -> [Binary p] #

randoms :: RandomGen g => g -> [Binary p] #

randomRIO :: (Binary p, Binary p) -> IO (Binary p) #

randomIO :: IO (Binary p) #

KnownNat p => Arbitrary (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

arbitrary :: Gen (Binary p) #

shrink :: Binary p -> [Binary p] #

Bits (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

(.&.) :: Binary p -> Binary p -> Binary p #

(.|.) :: Binary p -> Binary p -> Binary p #

xor :: Binary p -> Binary p -> Binary p #

complement :: Binary p -> Binary p #

shift :: Binary p -> Int -> Binary p #

rotate :: Binary p -> Int -> Binary p #

zeroBits :: Binary p #

bit :: Int -> Binary p #

setBit :: Binary p -> Int -> Binary p #

clearBit :: Binary p -> Int -> Binary p #

complementBit :: Binary p -> Int -> Binary p #

testBit :: Binary p -> Int -> Bool #

bitSizeMaybe :: Binary p -> Maybe Int #

bitSize :: Binary p -> Int #

isSigned :: Binary p -> Bool #

shiftL :: Binary p -> Int -> Binary p #

unsafeShiftL :: Binary p -> Int -> Binary p #

shiftR :: Binary p -> Int -> Binary p #

unsafeShiftR :: Binary p -> Int -> Binary p #

rotateL :: Binary p -> Int -> Binary p #

rotateR :: Binary p -> Int -> Binary p #

popCount :: Binary p -> Int #

NFData (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

rnf :: Binary p -> () #

KnownNat p => Group (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

invert :: Binary p -> Binary p #

pow :: Integral x => Binary p -> x -> Binary p #

Hashable (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

hashWithSalt :: Int -> Binary p -> Int #

hash :: Binary p -> Int #

KnownNat p => GcdDomain (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

divide :: Binary p -> Binary p -> Maybe (Binary p) #

gcd :: Binary p -> Binary p -> Binary p #

lcm :: Binary p -> Binary p -> Binary p #

coprime :: Binary p -> Binary p -> Bool #

KnownNat p => Field (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

KnownNat p => Euclidean (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

quotRem :: Binary p -> Binary p -> (Binary p, Binary p) #

quot :: Binary p -> Binary p -> Binary p #

rem :: Binary p -> Binary p -> Binary p #

degree :: Binary p -> Natural #

KnownNat p => Semiring (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

plus :: Binary p -> Binary p -> Binary p #

zero :: Binary p #

times :: Binary p -> Binary p -> Binary p #

one :: Binary p #

fromNatural :: Natural -> Binary p #

KnownNat p => Ring (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

negate :: Binary p -> Binary p #

KnownNat p => Pretty (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

pretty :: Binary p -> Doc #

prettyList :: [Binary p] -> Doc #

KnownNat p => GaloisField (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

KnownNat p => BinaryField (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

fromB :: Binary p -> Integer Source #

KnownNat p => TowerOfFields (Binary p) (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Binary p -> Binary p Source #

KnownNat p => TowerOfFields (Prime 2) (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Prime 2 -> Binary p Source #

type Rep (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

type Rep (Binary p) = D1 (MetaData "Binary" "Data.Field.Galois.Binary" "galois-field-1.0.0-YpVwDeebGU1udy5ZORBqg" True) (C1 (MetaCons "B" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))
type Item (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

type Item (Binary p) = Natural

class GaloisField k => BinaryField k Source #

Binary fields GF(2^q)[X]/<f(X)> for q positive and f(X) irreducible monic in GF(2^q)[X] encoded as an integer.

Minimal complete definition

fromB

Instances
KnownNat p => BinaryField (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Binary

Methods

fromB :: Binary p -> Integer Source #

fromB :: BinaryField k => k -> Integer Source #

Convert from GF(2^q)[X]/<f(X)> to Z.

toB :: KnownNat p => Integer -> Binary p Source #

Safe convert from Z to GF(2^q)[X]/<f(X)>.

toB' :: KnownNat p => Integer -> Binary p Source #

Unsafe convert from Z to GF(2^q)[X]/<f(X)>.

Square roots

qnr :: GaloisField k => Maybe k Source #

Get randomised quadratic nonresidue.

qr :: GaloisField k => k -> Bool Source #

Check if quadratic residue.

quad :: GaloisField k => k -> k -> k -> Maybe k Source #

Solve quadratic ax^2 + bx + c = 0 over field.

rnd :: (GaloisField k, MonadRandom m) => m k Source #

Randomised field element.

rndR :: (GaloisField k, MonadRandom m) => (k, k) -> m k Source #

Randomised field element in range.

sr :: GaloisField k => k -> Maybe k Source #

Square root of field element.

Towers of fields

class (GaloisField k, GaloisField l) => TowerOfFields k l where Source #

Tower of fields L over K strict partial ordering.

Methods

embed :: k -> l Source #

Embed K into L naturally.

Instances
(TowerOfFields k l, IrreducibleMonic p l, TowerOfFields l (Extension p l)) => TowerOfFields k (Extension p l) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: k -> Extension p l Source #

IrreducibleMonic p k => TowerOfFields k (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: k -> Extension p k Source #

KnownNat p => TowerOfFields (Binary p) (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Binary p -> Binary p Source #

KnownNat p => TowerOfFields (Prime p) (Prime p) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Prime p -> Prime p Source #

KnownNat p => TowerOfFields (Prime 2) (Binary p) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Prime 2 -> Binary p Source #

IrreducibleMonic p k => TowerOfFields (Extension p k) (Extension p k) Source # 
Instance details

Defined in Data.Field.Galois.Tower

Methods

embed :: Extension p k -> Extension p k Source #

(*^) :: TowerOfFields k l => k -> l -> l infixl 7 Source #

Scalar multiplication.

Roots of unity

class Group g => CyclicSubgroup g where Source #

Cyclic subgroups of finite groups.

Methods

gen :: g Source #

Generator of subgroup.

data RootsOfUnity (n :: Nat) k Source #

n-th roots of unity of Galois fields.

Instances
Functor (RootsOfUnity n) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

fmap :: (a -> b) -> RootsOfUnity n a -> RootsOfUnity n b #

(<$) :: a -> RootsOfUnity n b -> RootsOfUnity n a #

Eq k => Eq (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

(==) :: RootsOfUnity n k -> RootsOfUnity n k -> Bool #

(/=) :: RootsOfUnity n k -> RootsOfUnity n k -> Bool #

Ord k => Ord (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Show k => Show (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Generic (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Associated Types

type Rep (RootsOfUnity n k) :: Type -> Type #

Methods

from :: RootsOfUnity n k -> Rep (RootsOfUnity n k) x #

to :: Rep (RootsOfUnity n k) x -> RootsOfUnity n k #

(KnownNat n, GaloisField k) => Semigroup (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

(<>) :: RootsOfUnity n k -> RootsOfUnity n k -> RootsOfUnity n k #

sconcat :: NonEmpty (RootsOfUnity n k) -> RootsOfUnity n k #

stimes :: Integral b => b -> RootsOfUnity n k -> RootsOfUnity n k #

(KnownNat n, GaloisField k) => Monoid (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

(KnownNat n, GaloisField k, CyclicSubgroup (RootsOfUnity n k), Group (RootsOfUnity n k)) => Random (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

randomR :: RandomGen g => (RootsOfUnity n k, RootsOfUnity n k) -> g -> (RootsOfUnity n k, g) #

random :: RandomGen g => g -> (RootsOfUnity n k, g) #

randomRs :: RandomGen g => (RootsOfUnity n k, RootsOfUnity n k) -> g -> [RootsOfUnity n k] #

randoms :: RandomGen g => g -> [RootsOfUnity n k] #

randomRIO :: (RootsOfUnity n k, RootsOfUnity n k) -> IO (RootsOfUnity n k) #

randomIO :: IO (RootsOfUnity n k) #

(KnownNat n, GaloisField k, CyclicSubgroup (RootsOfUnity n k), Group (RootsOfUnity n k)) => Arbitrary (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

arbitrary :: Gen (RootsOfUnity n k) #

shrink :: RootsOfUnity n k -> [RootsOfUnity n k] #

Bits k => Bits (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

NFData k => NFData (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

rnf :: RootsOfUnity n k -> () #

(KnownNat n, GaloisField k) => Group (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

invert :: RootsOfUnity n k -> RootsOfUnity n k #

pow :: Integral x => RootsOfUnity n k -> x -> RootsOfUnity n k #

(KnownNat n, GaloisField k) => Pretty (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

Methods

pretty :: RootsOfUnity n k -> Doc #

prettyList :: [RootsOfUnity n k] -> Doc #

type Rep (RootsOfUnity n k) Source # 
Instance details

Defined in Data.Field.Galois.Unity

type Rep (RootsOfUnity n k) = D1 (MetaData "RootsOfUnity" "Data.Field.Galois.Unity" "galois-field-1.0.0-YpVwDeebGU1udy5ZORBqg" True) (C1 (MetaCons "U" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 k)))

cardinality :: forall n k. (KnownNat n, GaloisField k) => RootsOfUnity n k -> Natural Source #

Cardinality of subgroup.

cofactor :: forall n k. (KnownNat n, GaloisField k) => RootsOfUnity n k -> Natural Source #

Cofactor of subgroup in group.

isPrimitiveRootOfUnity :: (KnownNat n, GaloisField k) => RootsOfUnity n k -> Bool Source #

Check if element is primitive root of unity.

isRootOfUnity :: (KnownNat n, GaloisField k) => RootsOfUnity n k -> Bool Source #

Check if element is root of unity.

toU :: forall n k. (KnownNat n, GaloisField k) => k -> RootsOfUnity n k Source #

Safe convert from field to roots of unity.

toU' :: forall n k. (KnownNat n, GaloisField k) => k -> RootsOfUnity n k Source #

Unsafe convert from field to roots of unity.