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

Math.FiniteField.GaloisField.Zech.C

Description

C implementation of GF(p^m) via precomputed tables of Zech's logarithm.

This way I can test the C implementation using the Haskell test framework.

Synopsis

Documentation

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

Constructors

WitnessC (ForeignPtr Int32) 

Instances

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

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

show :: WitnessC p m -> String #

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

data SomeWitnessC Source #

Constructors

forall p m. SomeWitnessC (WitnessC p m) 

Instances

Instances details
Show SomeWitnessC Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

saveCZechTable :: FilePath -> WitnessC p q -> IO () Source #

Save the data necessary to do computations to a file

loadCZechTable :: FilePath -> IO (Maybe SomeWitnessC) Source #

Load the data necessary to do computations from a file

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

An element of the field

Constructors

CFq !(ForeignPtr Int32) !Int32 

Instances

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

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

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

Fractional (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

recip :: CFq p m -> CFq p m #

fromRational :: Rational -> CFq p m #

Num (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

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

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

negate :: CFq p m -> CFq p m #

abs :: CFq p m -> CFq p m #

signum :: CFq p m -> CFq p m #

fromInteger :: Integer -> CFq p m #

Ord (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

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

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

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

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

max :: CFq p m -> CFq p m -> CFq p m #

min :: CFq p m -> CFq p m -> CFq p m #

Show (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

show :: CFq p m -> String #

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

Field (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

Associated Types

type Witness (CFq p m) = (w :: Type) Source #

type Prime (CFq p m) :: Nat Source #

type Dim (CFq p m) :: Nat Source #

Methods

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

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

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

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

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

isZero :: CFq p m -> Bool Source #

isOne :: CFq p m -> Bool Source #

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

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

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

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

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

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

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

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

frobenius :: CFq p m -> CFq p m Source #

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

type Witness (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

type Witness (CFq p m) = WitnessC p m
type Prime (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

type Prime (CFq p m) = p
type Dim (CFq p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

type Dim (CFq p m) = m

randomCFq :: RandomGen gen => WitnessC p m -> gen -> (CFq p m, gen) Source #

randomInvCFq :: RandomGen gen => WitnessC p m -> gen -> (CFq p m, gen) Source #

The "raw" interface, where you have to manually supply the tables

newtype Raw (p :: Nat) (m :: Nat) Source #

Constructors

Raw Int32 

Instances

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

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

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

Ord (Raw p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

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

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

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

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

max :: Raw p m -> Raw p m -> Raw p m #

min :: Raw p m -> Raw p m -> Raw p m #

Show (Raw p m) Source # 
Instance details

Defined in Math.FiniteField.GaloisField.Zech.C

Methods

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

show :: Raw p m -> String #

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

rawNeg :: WitnessC p m -> Raw p m -> Raw p m Source #

rawAdd :: WitnessC p m -> Raw p m -> Raw p m -> Raw p m Source #

rawSub :: WitnessC p m -> Raw p m -> Raw p m -> Raw p m Source #

rawInv :: WitnessC p m -> Raw p m -> Raw p m Source #

rawMul :: WitnessC p m -> Raw p m -> Raw p m -> Raw p m Source #

rawDiv :: WitnessC p m -> Raw p m -> Raw p m -> Raw p m Source #

rawPow :: WitnessC p m -> Raw p m -> Int -> Raw p m Source #

rawEmbed :: WitnessC p m -> Int -> Raw p m Source #

rawEnumerate :: WitnessC p m -> [Raw p m] Source #

foreign imports