Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basic (unoptimized) finite field arithmetic.
- data GF fp d
- type PrimeField fp = (Enumerable fp, Field fp, Eq fp, ZeroTestable fp, Prim (CharOf fp), IrreduciblePoly fp)
- type GFCtx fp d = (PrimeField fp, Reflects d Int)
- size :: GFCtx fp d => Tagged (GF fp d) Int
- trace :: forall fp d. GFCtx fp d => GF fp d -> fp
- toList :: forall fp d. (Reflects d Int, Additive fp) => GF fp d -> [fp]
- fromList :: forall fp d. Reflects d Int => [fp] -> GF fp d
- class Field fp => IrreduciblePoly fp where
- irreduciblePoly :: Reflects d Int => Tagged d (Polynomial fp)
- data X = X
- (^^) :: Ring a => X -> Int -> Polynomial a
- newtype TensorCoeffs a = Coeffs {
- unCoeffs :: [a]
Documentation
A finite field of given degree over F_p
.
(Eq fp, C fp) => Eq (GF k fp d) Source | |
Show fp => Show (GF k fp d) Source | |
NFData fp => NFData (GF k fp d) Source | |
GFCtx k fp d => C (GF k fp d) Source | |
GFCtx k fp d => C (GF k fp d) Source | |
C fp => C (GF k fp d) Source | |
C fp => C (GF k fp d) Source | |
GFCtx k fp d => Enumerable (GF k fp d) Source | |
GFCtx k fp d => CRTrans (GF k fp d) Source | |
(Additive fp, Ring (GF k fp d), Reflects k d Int) => C (GF k fp d) (TensorCoeffs fp) Source | |
(GFCtx k fp d, Fact m, Additive (CT m fp)) => C (GF k fp d) (CT m fp) | |
(GFCtx k fp d, Fact m, Additive (RT m fp)) => C (GF k fp d) (RT m fp) | |
(GFCtx k fp d, Fact m, CElt t fp) => C (GF k fp d) (Cyc t m fp) | |
(GFCtx k fp d, Fact m, UCElt t fp) => C (GF k fp d) (UCyc Factored t m P fp) |
type PrimeField fp = (Enumerable fp, Field fp, Eq fp, ZeroTestable fp, Prim (CharOf fp), IrreduciblePoly fp) Source
type GFCtx fp d = (PrimeField fp, Reflects d Int) Source
toList :: forall fp d. (Reflects d Int, Additive fp) => GF fp d -> [fp] Source
Yield a list of length exactly d
(i.e., including trailing zeros)
of the fp
-coefficients with respect to the power basis
fromList :: forall fp d. Reflects d Int => [fp] -> GF fp d Source
Yield a field element given up to d
coefficients with respect
to the power basis.
class Field fp => IrreduciblePoly fp where Source
Represents fields over which we can get irreducible
polynomials of desired degrees. (An instance of this class is
defined in IrreducibleChar2
and exported from
Lol
.)
irreduciblePoly :: Reflects d Int => Tagged d (Polynomial fp) Source
(^^) :: Ring a => X -> Int -> Polynomial a Source
Convenience function for writing IrreduciblePoly
instances.