Copyright | (c) Wanja Chresta 2018 |
---|---|
License | GPL-3 |
Maintainer | wanja dit hs at chrummibei dot ch |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Some finite field parameters are missing from HaskellForMaths
implementation.
Here, we add type classes to add these parameters to the type level.
Synopsis
- type family Characteristic (f :: *) :: Nat
- char :: forall c f. (KnownNat c, c ~ Characteristic f) => Proxy f -> Int
- type family PolyDegree (f :: *) :: Nat
- type family Size (f :: *) :: Nat
Documentation
type family Characteristic (f :: *) :: Nat Source #
The characteristic of a finite field on the type level. The characteristic
is: For any element x
in the field f
with characteristic c
, we have:
c * x = x + x + .. + x (c times) = 0
Instances
char :: forall c f. (KnownNat c, c ~ Characteristic f) => Proxy f -> Int Source #
Characteristic of a field. It takes a finite field type in the proxy
value and gives the characteristic. This is done using type families
To support new finite field types, you need to add a type instance
for the type family Characteristic
.
type family PolyDegree (f :: *) :: Nat Source #
Type family which gives the degree of a polynomial type. This is used to
extract type level information from Extension
Instances
type PolyDegree ConwayF4 Source # | |
Defined in Math.Algebra.Field.Static | |
type PolyDegree ConwayF8 Source # | |
Defined in Math.Algebra.Field.Static | |
type PolyDegree ConwayF9 Source # | |
Defined in Math.Algebra.Field.Static | |
type PolyDegree ConwayF16 Source # | |
Defined in Math.Algebra.Field.Static | |
type PolyDegree ConwayF25 Source # | |
Defined in Math.Algebra.Field.Static | |
type PolyDegree ConwayF27 Source # | |
Defined in Math.Algebra.Field.Static | |
type PolyDegree ConwayF32 Source # | |
Defined in Math.Algebra.Field.Static |
type family Size (f :: *) :: Nat Source #
Type family which gives the size of a field, i.e. the number of elements of a finite field.
Instances
type Size (Fp p) Source # | |
Defined in Math.Algebra.Field.Static | |
type Size (ExtensionField fp poly) Source # | |
Defined in Math.Algebra.Field.Static |