lol-0.7.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2017
Chris Peikert 2011-2017
LicenseGPL-3
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 fp d, NFData fp) => CRTrans Maybe (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

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

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

Defined in Crypto.Lol.Types.FiniteField

Methods

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

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

Show fp => Show (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

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

show :: GF fp d -> String #

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

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

Defined in Crypto.Lol.Types.FiniteField

Methods

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

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

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

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

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

randomIO :: IO (GF fp d) #

NFData fp => NFData (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

rnf :: GF fp d -> () #

GFCtx fp d => C (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

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

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

fromRational' :: Rational -> GF fp d #

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

GFCtx fp d => C (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

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

one :: GF fp d #

fromInteger :: Integer -> GF fp d #

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

C fp => C (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

isZero :: GF fp d -> Bool #

C fp => C (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

zero :: GF fp d #

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

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

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

GFCtx fp d => Enumerable (GF fp d) Source # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

Methods

values :: [GF fp d] Source #

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

Defined in Crypto.Lol.Types.FiniteField

Methods

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

(Ring (GF (ZqBasic q z) d), Module (GF (ZqBasic q z) d) (CycG t m (ZqBasic q z))) => C (GF (ZqBasic q z) d) (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(*>) :: GF (ZqBasic q z) d -> Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) #

(GFCtx fp d, Fact m, TensorPowDec t fp, Module (GF fp d) (t m fp)) => C (GF fp d) (CycRep t P m fp) Source #

\(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.

Instance details

Defined in Crypto.Lol.Cyclotomic.CycRep

Methods

(*>) :: GF fp d -> CycRep t P m fp -> CycRep t P m 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.)

Instances
((CharOf a :: PrimeBin) ~ Prime2, Field a) => IrreduciblePoly a Source # 
Instance details

Defined in Crypto.Lol.Types.IrreducibleChar2

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 # 
Instance details

Defined in Crypto.Lol.Types.FiniteField

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

Defined in Crypto.Lol.Types.FiniteField

Methods

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