lol-0.6.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2017
Chris Peikert 2011-2017
LicenseGPL-2
Maintainerecrockett0@email.com
Stabilityexperimental
PortabilityPOSIX \( \def\F{\mathbb{F}} \)
Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Types.FiniteField

Description

Basic (unoptimized) finite field arithmetic.

Synopsis

Documentation

data GF fp d Source #

A finite field of given degree over \(\F_p\).

Instances

GFCtx k fp d => CRTrans Maybe (GF k fp d) Source # 

Methods

crtInfo :: Reflects k1 m Int => TaggedT * k1 m Maybe (CRTInfo (GF k fp d)) Source #

(C fp, Eq fp) => Eq (GF k fp d) Source # 

Methods

(==) :: GF k fp d -> GF k fp d -> Bool #

(/=) :: GF k fp d -> GF k fp d -> Bool #

Show fp => Show (GF k fp d) Source # 

Methods

showsPrec :: Int -> GF k fp d -> ShowS #

show :: GF k fp d -> String #

showList :: [GF k fp d] -> ShowS #

(Random fp, Reflects k d Int) => Random (GF k fp d) Source # 

Methods

randomR :: RandomGen g => (GF k fp d, GF k fp d) -> g -> (GF k fp d, g) #

random :: RandomGen g => g -> (GF k fp d, g) #

randomRs :: RandomGen g => (GF k fp d, GF k fp d) -> g -> [GF k fp d] #

randoms :: RandomGen g => g -> [GF k fp d] #

randomRIO :: (GF k fp d, GF k fp d) -> IO (GF k fp d) #

randomIO :: IO (GF k fp d) #

NFData fp => NFData (GF k fp d) Source # 

Methods

rnf :: GF k fp d -> () #

GFCtx k fp d => C (GF k fp d) Source # 

Methods

(/) :: GF k fp d -> GF k fp d -> GF k fp d #

recip :: GF k fp d -> GF k fp d #

fromRational' :: Rational -> GF k fp d #

(^-) :: GF k fp d -> Integer -> GF k fp d #

C fp => C (GF k fp d) Source # 

Methods

isZero :: GF k fp d -> Bool #

GFCtx k fp d => C (GF k fp d) Source # 

Methods

(*) :: GF k fp d -> GF k fp d -> GF k fp d #

one :: GF k fp d #

fromInteger :: Integer -> GF k fp d #

(^) :: GF k fp d -> Integer -> GF k fp d #

C fp => C (GF k fp d) Source # 

Methods

zero :: GF k fp d #

(+) :: GF k fp d -> GF k fp d -> GF k fp d #

(-) :: GF k fp d -> GF k fp d -> GF k fp d #

negate :: GF k fp d -> GF k fp d #

GFCtx k fp d => Enumerable (GF k fp d) Source # 

Methods

values :: [GF k fp d] Source #

(Additive fp, Ring (GF k fp d), Reflects k d Int) => C (GF k fp d) (TensorCoeffs fp) Source # 

Methods

(*>) :: GF k fp d -> TensorCoeffs fp -> TensorCoeffs fp #

(GFCtx k fp d, Fact m, CElt t fp) => C (GF k fp d) (Cyc t m fp) #

\(R_p\) is an \(\F_{p^d}\)-module when \(d\) divides \(\varphi(m)\), by applying \(d\)-dimensional \(\F_p\)-linear transform on \(d\)-dim chunks of powerful basis coeffs.

Methods

(*>) :: GF k fp d -> Cyc t m fp -> Cyc t m fp #

(GFCtx k fp d, Fact m, Tensor t, TElt t fp) => C (GF k fp d) (UCyc t m P fp) #

\(R_p\) is an \(\F_{p^d}\)-module when \(d\) divides \(\varphi(m)\), by applying \(d\)-dimensional \(\F_p\)-linear transform on \(d\)-dim chunks of powerful basis coeffs.

Methods

(*>) :: GF k fp d -> UCyc t m P fp -> UCyc t m P fp #

type PrimeField fp = (Enumerable fp, Field fp, Eq fp, ZeroTestable fp, Prime (CharOf fp), IrreduciblePoly fp) Source #

Constraint synonym for a prime field.

type GFCtx fp d = (PrimeField fp, Reflects d Int) Source #

Constraint synonym for a finite field.

size :: GFCtx fp d => Tagged (GF fp d) Int Source #

The order of the field: size (GF fp d) = \( p^d \)

trace :: forall fp d. GFCtx fp d => GF fp d -> fp Source #

Trace into the prime subfield.

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 \(\F_p\)-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 Crypto.Lol.Types.IrreducibleChar2 and exported from Crypto.Lol.Types.)

Minimal complete definition

irreduciblePoly

data X Source #

Convenience data type for writing IrreduciblePoly instances.

Constructors

X 

(^^) :: Ring a => X -> Int -> Polynomial a Source #

Convenience function for writing IrreduciblePoly instances.

newtype TensorCoeffs a Source #

This wrapper for a list of coefficients is used to define a \(\F_{p^d}\)-module structure for tensors over \(\F_p\) of dimension \(n\), where \(d \mid n\).

Constructors

Coeffs 

Fields

Instances

C a => C (TensorCoeffs a) Source # 
(Additive fp, Ring (GF k fp d), Reflects k d Int) => C (GF k fp d) (TensorCoeffs fp) Source # 

Methods

(*>) :: GF k fp d -> TensorCoeffs fp -> TensorCoeffs fp #