Safe Haskell | None |
---|---|
Language | Haskell2010 |
An implementation of cyclotomic rings with safe interface:
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
.
- data Cyc t m r
- type CElt t r = (Tensor t, RElt t r, RElt t (CRTExt r), CRTEmbed r, Eq r, Random r)
- cyc :: UCyc t m r -> Cyc t m r
- unsafeUnCyc :: Cyc t m r -> UCyc t m r
- mulG :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r
- divG :: (Fact m, CElt t r) => Cyc t m r -> Maybe (Cyc t m r)
- scalarCyc :: (Fact m, CElt t a) => a -> Cyc t m a
- liftCyc :: (Lift b a, Fact m, CElt t a, CElt t b) => Basis -> Cyc t m b -> Cyc t m a
- advisePow :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r
- adviseDec :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r
- adviseCRT :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r
- tGaussian :: (Fact m, OrdFloat q, Random q, CElt t q, ToRational v, MonadRandom rnd) => v -> rnd (Cyc t m q)
- errorRounded :: (ToInteger z, Fact m, CElt t z, ToRational v, MonadRandom rnd) => v -> rnd (Cyc t m z)
- 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)
- embed :: (m `Divides` m', CElt t r) => Cyc t m r -> Cyc t m' r
- twace :: (m `Divides` m', CElt t r) => Cyc t m' r -> Cyc t m r
- powBasis :: (m `Divides` m', CElt t r) => Tagged m [Cyc t m' r]
- crtSet :: (m `Divides` m', ZPP r, CElt t r, CElt t (ZPOf r)) => Tagged m [Cyc t m' r]
- coeffsCyc :: (m `Divides` m', CElt t r) => Basis -> Cyc t m' r -> [Cyc t m r]
- module Crypto.Lol.Cyclotomic.Utility
Data type
Wrapper around UCyc
that exposes a narrower, safe interface.
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 | |
(Random r, SingI Factored m, C r, C r, CRTrans r, Tensor t, TElt t r) => Random (Cyc t m r) Source | |
Arbitrary (t m r) => Arbitrary (Cyc t m r) Source | |
NFData (UCyc t m a) => NFData (Cyc t m a) 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 |
unsafeUnCyc :: Cyc t m r -> UCyc t m r Source
Unsafe deconstructor for Cyc
.
Basic operations
mulG :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r Source
Multiply by the special element g
of the m
th 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 implementation is not a constant-time algorithm, so
information about the argument may be leaked through a timing
channel.
scalarCyc :: (Fact m, CElt t a) => a -> Cyc t m a Source
Embed a scalar from the base ring as a cyclotomic element.
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.
advisePow :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r Source
Same as adviseCRT
, but for the powerful-basis representation.
adviseDec :: (Fact m, CElt t r) => Cyc t m r -> Cyc t m r Source
Same as adviseCRT
, but for the powerful-basis representation.
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.
Error sampling
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 may not be sufficient for rigorous proof-based
security.
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.
Sub/extension rings
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.