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
Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Gadget

Description

Interfaces for "gadgets," decomposition, and error correction.

Synopsis

Documentation

class Ring u => Gadget gad u where Source #

Gadget vectors, parameterized by an index type.

Minimal complete definition

gadget

Methods

gadget :: [u] Source #

The gadget vector over u.

encode :: u -> [u] Source #

Yield an error-tolerant encoding of an element with respect to the gadget. (Mathematically, this should just be the product of the input with the gadget, but it is a class method to allow for optimized implementations.)

Instances
(Gadget gad a, Gadget gad b) => Gadget (gad :: k) (a, b) Source #

Product ring: concatenate gadgets over component rings

Instance details

Defined in Crypto.Lol.Gadget

Methods

gadget :: [(a, b)] Source #

encode :: (a, b) -> [(a, b)] Source #

(Gadget gad (Cyc t m a), Gadget gad (Cyc t m b)) => Gadget (gad :: k) (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

gadget :: [Cyc t m (a, b)] Source #

encode :: Cyc t m (a, b) -> [Cyc t m (a, b)] Source #

Gadget gad (CycG t m (ZqBasic q z)) => Gadget (gad :: k2) (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

gadget :: [Cyc t m (ZqBasic q z)] Source #

encode :: Cyc t m (ZqBasic q z) -> [Cyc t m (ZqBasic q z)] Source #

(Reflects q z, ToInteger z) => Gadget TrivGad (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

gadget :: [ZqBasic q z] Source #

encode :: ZqBasic q z -> [ZqBasic q z] Source #

(Reflects q z, ToInteger z, RealIntegral z, Reflects b z) => Gadget (BaseBGad b :: Type) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

gadget :: [ZqBasic q z] Source #

encode :: ZqBasic q z -> [ZqBasic q z] Source #

class (Gadget gad u, Reduce (DecompOf u) u) => Decompose gad u where Source #

Decomposition relative to a gadget.

Associated Types

type DecompOf u Source #

The ring that u decomposes over.

Methods

decompose :: u -> [DecompOf u] Source #

Yield a short vector \( x \) such that \( \langle g, x\rangle = u \).

Instances
(Decompose gad a, Decompose gad b, DecompOf a ~ DecompOf b) => Decompose (gad :: k) (a, b) Source #

Product ring: concatenate decompositions for component rings

Instance details

Defined in Crypto.Lol.Gadget

Associated Types

type DecompOf (a, b) :: Type Source #

Methods

decompose :: (a, b) -> [DecompOf (a, b)] Source #

(Decompose gad (Cyc t m a), Decompose gad (Cyc t m b), DecompOf (Cyc t m a) ~ DecompOf (Cyc t m b), Reduce (DecompOf (Cyc t m a)) (Cyc t m (a, b))) => Decompose (gad :: k) (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type DecompOf (Cyc t m (a, b)) :: Type Source #

Methods

decompose :: Cyc t m (a, b) -> [DecompOf (Cyc t m (a, b))] Source #

(Decompose gad (CycG t m (ZqBasic q Int64)), Reduce (Cyc t m Int64) (Cyc t m (ZqBasic q Int64))) => Decompose (gad :: k2) (Cyc t m (ZqBasic q Int64)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type DecompOf (Cyc t m (ZqBasic q Int64)) :: Type Source #

Methods

decompose :: Cyc t m (ZqBasic q Int64) -> [DecompOf (Cyc t m (ZqBasic q Int64))] Source #

(Reflects q z, ToInteger z) => Decompose TrivGad (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Associated Types

type DecompOf (ZqBasic q z) :: Type Source #

Methods

decompose :: ZqBasic q z -> [DecompOf (ZqBasic q z)] Source #

(Reflects q z, ToInteger z, Reflects b z) => Decompose (BaseBGad b :: Type) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Associated Types

type DecompOf (ZqBasic q z) :: Type Source #

Methods

decompose :: ZqBasic q z -> [DecompOf (ZqBasic q z)] Source #

class Gadget gad u => Correct gad u where Source #

Error correction relative to a gadget.

Methods

correct :: [u] -> (u, [LiftOf u]) Source #

Error-correct a "noisy" encoding of an element (see encode), returning the encoded element and the error vector.

Instances
(Correct gad a, Correct gad b, Mod a, Mod b, Field a, Field b, Lift' a, Lift' b, ToInteger (LiftOf a), ToInteger (LiftOf b)) => Correct (gad :: k) (a, b) Source #

Product ring

Instance details

Defined in Crypto.Lol.Gadget

Methods

correct :: [(a, b)] -> ((a, b), [LiftOf (a, b)]) Source #

Correct gad (CycG t m (ZqBasic q Int64)) => Correct (gad :: k2) (Cyc t m (ZqBasic q Int64)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

correct :: [Cyc t m (ZqBasic q Int64)] -> (Cyc t m (ZqBasic q Int64), [LiftOf (Cyc t m (ZqBasic q Int64))]) Source #

(Reflects q z, ToInteger z, Ring z) => Correct TrivGad (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

correct :: [ZqBasic q z] -> (ZqBasic q z, [LiftOf (ZqBasic q z)]) Source #

(Reflects q z, ToInteger z, Reflects b z) => Correct (BaseBGad b :: Type) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

correct :: [ZqBasic q z] -> (ZqBasic q z, [LiftOf (ZqBasic q z)]) Source #

decomposeList :: forall gad u. Decompose gad u => [u] -> [DecompOf u] Source #

Decompose a list entry-wise.

decomposeMatrix :: forall gad u. Decompose gad u => Matrix u -> Matrix (DecompOf u) Source #

Decompose a matrix entry-wise.

data TrivGad Source #

Dummy type representing the gadget \( [1] \).

Instances
(Reflects q z, ToInteger z, Ring z) => Correct TrivGad (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

correct :: [ZqBasic q z] -> (ZqBasic q z, [LiftOf (ZqBasic q z)]) Source #

(Reflects q z, ToInteger z) => Decompose TrivGad (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Associated Types

type DecompOf (ZqBasic q z) :: Type Source #

Methods

decompose :: ZqBasic q z -> [DecompOf (ZqBasic q z)] Source #

(Reflects q z, ToInteger z) => Gadget TrivGad (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

gadget :: [ZqBasic q z] Source #

encode :: ZqBasic q z -> [ZqBasic q z] Source #

Show (ArgType TrivGad) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType

data BaseBGad b Source #

Dummy type representing the gadget \( [1,b,b^2,\ldots] \).

Instances
(Reflects q z, ToInteger z, Reflects b z) => Correct (BaseBGad b :: Type) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

correct :: [ZqBasic q z] -> (ZqBasic q z, [LiftOf (ZqBasic q z)]) Source #

(Reflects q z, ToInteger z, Reflects b z) => Decompose (BaseBGad b :: Type) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Associated Types

type DecompOf (ZqBasic q z) :: Type Source #

Methods

decompose :: ZqBasic q z -> [DecompOf (ZqBasic q z)] Source #

(Reflects q z, ToInteger z, RealIntegral z, Reflects b z) => Gadget (BaseBGad b :: Type) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Types.Unsafe.ZqBasic

Methods

gadget :: [ZqBasic q z] Source #

encode :: ZqBasic q z -> [ZqBasic q z] Source #

Reflects b Integer => Show (ArgType (BaseBGad b)) Source # 
Instance details

Defined in Crypto.Lol.Utils.ShowType