Safe Haskell | None |
---|---|
Language | Haskell2010 |
Type class interface to different implementations of finite fields
Synopsis
- class (Eq f, Ord f, Show f, Num f, Fractional f, Show (Witness f)) => Field f where
- type Witness f = w | w -> f
- type Prime f :: Nat
- type Dim f :: Nat
- characteristic :: Witness f -> Integer
- dimension :: Witness f -> Integer
- fieldSize :: Witness f -> Integer
- zero :: Witness f -> f
- one :: Witness f -> f
- isZero :: f -> Bool
- isOne :: f -> Bool
- embed :: Witness f -> Integer -> f
- embedSmall :: Witness f -> Int -> f
- randomFieldElem :: RandomGen gen => Witness f -> gen -> (f, gen)
- randomInvertible :: RandomGen gen => Witness f -> gen -> (f, gen)
- primGen :: Witness f -> f
- witnessOf :: f -> Witness f
- power :: f -> Integer -> f
- powerSmall :: f -> Int -> f
- frobenius :: f -> f
- enumerate :: Witness f -> [f]
- fieldPrimeSNat :: Field f => Witness f -> SNat (Prime f)
- fieldPrimeSNat64 :: Field f => Witness f -> SNat64 (Prime f)
- fieldDimSNat :: Field f => Witness f -> SNat (Dim f)
- fieldDimSNat64 :: Field f => Witness f -> SNat64 (Dim f)
- data SomeField = forall f.Field f => SomeField (Witness f)
- fieldName :: Field f => Witness f -> String
- inverse :: Field f => f -> f
- enumPrimeField :: forall f. Field f => Witness f -> [f]
- multGroup :: Field f => Witness f -> [f]
- discreteLogTable :: forall f. Field f => Witness f -> Map f Int
- powerDefault :: forall f. Field f => f -> Integer -> f
Fields
class (Eq f, Ord f, Show f, Num f, Fractional f, Show (Witness f)) => Field f where Source #
A class for field element types
type Witness f = w | w -> f Source #
witness for the existence of the field (this is an injective type family!)
the characteristic at type level
the dimension at type level
characteristic :: Witness f -> Integer Source #
the prime characteristic
dimension :: Witness f -> Integer Source #
dimension over the prime field (the exponent m
in q=p^m
)
fieldSize :: Witness f -> Integer Source #
the size (or order) of the field
zero :: Witness f -> f Source #
The additive identity of the field
one :: Witness f -> f Source #
The multiplicative identity of the field
check for equality with the additive identity
check for equality with the multiplicative identity
embed :: Witness f -> Integer -> f Source #
an element of the prime field
embedSmall :: Witness f -> Int -> f Source #
randomFieldElem :: RandomGen gen => Witness f -> gen -> (f, gen) Source #
a uniformly random field element
randomInvertible :: RandomGen gen => Witness f -> gen -> (f, gen) Source #
a random invertible element
primGen :: Witness f -> f Source #
a primitive generator
witnessOf :: f -> Witness f Source #
extract t he witness from a field element
power :: f -> Integer -> f Source #
exponentiation
powerSmall :: f -> Int -> f Source #
Frobenius automorphism x -> x^p
enumerate :: Witness f -> [f] Source #
list of field elements (of course it's only useful for very small fields)
Instances
Some generic functions
enumPrimeField :: forall f. Field f => Witness f -> [f] Source #
Enumerate the elements of the prime field only
multGroup :: Field f => Witness f -> [f] Source #
The nonzero elements in cyclic order, starting from the primitive generator (of course this is only useful for very small fields)
discreteLogTable :: forall f. Field f => Witness f -> Map f Int Source #
Computes a table of discrete logarithms with respect to the primitive generator. Note: zero (that is, the additive identitiy of the field) is not present in the resulting map.
powerDefault :: forall f. Field f => f -> Integer -> f Source #
Generic exponentiation