lol-0.0.1.0: A library for lattice cryptography.

Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Cyclotomic.Cyc

Description

An implementation of cyclotomic rings. All functions and instances involving Cyc expose nothing about the internal representations of ring elements (e.g., the basis they are represented in). For an experts-only, "unsafe" implementation that offers limited exposure of internal representation, use UCyc.

Synopsis

Documentation

data Cyc t m r Source

Wrapper around UCyc that exposes a narrower, safe interface.

Instances

Correct k gad (UCyc t m a) => Correct k gad (Cyc t m a) Source 
(Decompose k gad (UCyc t m zq), Reduce (Cyc t m (DecompOf zq)) (Cyc t m zq)) => Decompose k gad (Cyc t m zq) Source 
Gadget k gad (UCyc t m a) => Gadget k gad (Cyc t m a) Source 
RescaleCyc (UCyc t) a b => RescaleCyc (Cyc t) a b Source 
Eq (UCyc t m a) => Eq (Cyc t m a) Source 
Show (UCyc t m a) => Show (Cyc t m a) Source 
(SingI Factored m, CRTrans r, Tensor t, TElt t r) => Random (Cyc t m r) Source 
Arbitrary (t m r) => Arbitrary (Cyc t m r) Source 
(NFData r, SingI Factored m, Tensor t, TElt t r, TElt t (CRTExt r)) => NFData (Cyc t m r) Source 
Ring (UCyc t m a) => C (Cyc t m a) Source 
(ToSDCtx t m' zp zq, Additive (CT m zp (Cyc t m' zq))) => C (CT m zp (Cyc t m' zq)) 
Additive (UCyc t m a) => C (Cyc t m a) Source 
(Eq zp, Divides m m', ToSDCtx t m' zp zq) => C (CT m zp (Cyc t m' zq)) 
(Reduce a b, Fact m, CElt t a, CElt t b) => Reduce (Cyc t m a) (Cyc t m b) Source 
type DecompOf (Cyc t m zq) = Cyc t m (DecompOf zq) Source 

type CElt t r = (Tensor t, CRTrans r, CRTrans (CRTExt r), CRTEmbed r, ZeroTestable r, TElt t r, TElt t (CRTExt r), Eq r, NFData r) Source

Shorthand for frequently reused constraints that are needed for most functions involving UCyc and Cyc.

cyc :: UCyc t m r -> Cyc t m r Source

Smart constructor (to prevent clients from pattern-matching).

unsafeUnCyc :: Cyc t m r -> UCyc t m r Source

Unsafe deconstructor for Cyc.

mulG :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r Source

Multiply by the special element g of the mth cyclotomic.

divG :: (Fact m, CElt t r) => Cyc t m r -> Maybe (Cyc t m r) Source

Divide by g, returning Nothing if not evenly divisible. WARNING: this is not a constant-time operation, so information about the argument may be leaked through a timing channel.

tGaussian :: (Fact m, OrdFloat q, Random q, CElt t q, ToRational v, MonadRandom rnd) => v -> rnd (Cyc t m q) Source

Sample from the "tweaked" Gaussian error distribution t*D in the decoding basis, where D has scaled variance v. Note: This implementation uses Double precision to generate the Gaussian sample, which is not cryptographically secure.

errorRounded :: (ToInteger z, Fact m, CElt t z, ToRational v, MonadRandom rnd) => v -> rnd (Cyc t m z) Source

Generate an LWE error term with given scaled variance, deterministically rounded in the decoding basis.

errorCoset :: (Mod zp, z ~ ModRep zp, Lift zp z, Fact m, CElt t zp, CElt t z, ToRational v, MonadRandom rnd) => v -> Cyc t m zp -> rnd (Cyc t m z) Source

Generate an LWE error term with given scaled variance * p^2 over the given coset, deterministically rounded in the decoding basis.

embed :: (m `Divides` m', CElt t r) => Cyc t m r -> Cyc t m' r Source

Embed into the extension ring.

twace :: (m `Divides` m', CElt t r) => Cyc t m' r -> Cyc t m r Source

The "tweaked trace" (twace) function Tw(x) = (mhat / m'hat) * Tr(g' / g * x), which fixes R pointwise (i.e., twace . embed == id).

powBasis :: (m `Divides` m', CElt t r) => Tagged m [Cyc t m' r] Source

The relative powerful basis of O_m' / O_m.

crtSet :: (m `Divides` m', ZPP r, CElt t r, CElt t (ZPOf r)) => Tagged m [Cyc t m' r] Source

The relative mod-r "CRT set" of the extension.

coeffsCyc :: (m `Divides` m', CElt t r) => Basis -> Cyc t m' r -> [Cyc t m r] Source

Return the given element's coefficient vector with respect to the (relative) powerful/decoding basis of the cyclotomic extension O_m' / O_m.

adviseCRT :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r Source

Yield an equivalent element that may be in a CRT representation. This can serve as an optimization hint. E.g., call adviseCRT prior to multiplying the same value by many other values.

liftCyc :: (Lift b a, Fact m, CElt t a, CElt t b) => Basis -> Cyc t m b -> Cyc t m a Source

Lift in the specified basis.

scalarCyc :: (Fact m, CElt t a) => a -> Cyc t m a Source

Embed a scalar from the base ring as a cyclotomic element.