lol-0.0.1.0: A general-purpose library for lattice cryptography.

Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Cyclotomic.UCyc

Contents

Description

An implementation of cyclotomic rings. WARNING: this module provides an experts-only, "unsafe" interface that may result in runtime errors if not used correctly! Cyc provides a safe interface, and should be used in applications whenever possible.

UCyc transparently handles all necessary conversions between internal representations to support fast ring operations, and efficiently stores and operates upon elements that are known to reside in subrings.

The Functor, Applicative, Foldable, and Traversable instances of UCyc, as well as the fmapC and fmapCM functions, work over the element's current r-basis representation (or pure scalar representation as a special case, to satisfy the Applicative laws), and the output remains in that representation. If the input's representation is not one of these, the behavior is a runtime error. To ensure a valid representation when using the methods from these classes, first call forceBasis or one of its specializations (forcePow, forceDec, forceAny).

Synopsis

Data type

data UCyc t m r Source

A data type for representing cyclotomic rings such as Z[zeta], Zq[zeta], and Q(zeta): t is the Tensor type for storing coefficients; m is the cyclotomic index; r is the base ring of the coefficients (e.g., Z, Zq).

Instances

(Correct k gad zq, Fact m, CElt t zq) => Correct k gad (UCyc t m zq) Source 
(Decompose k gad zq, Fact m, CElt t zq, Reduce (UCyc t m (DecompOf zq)) (UCyc t m zq)) => Decompose k gad (UCyc t m zq) Source 
(Gadget k gad zq, Fact m, CElt t zq) => Gadget k gad (UCyc t m zq) Source 
(Rescale a b, CElt t a, CElt t b) => RescaleCyc (UCyc t) a b Source 
(Mod a, Field b, Lift a z, Reduce z b, CElt t a, CElt t b, CElt t (a, b), CElt t z) => RescaleCyc (UCyc t) (a, b) b Source 
(Tensor t, Fact m) => Functor (UCyc t m) Source 
(Tensor t, Fact m) => Applicative (UCyc t m) Source 
(Tensor t, Fact m) => Foldable (UCyc t m) Source 
(Tensor t, Fact m) => Traversable (UCyc t m) Source 
(UCCtx t r, Fact m, Eq r) => Eq (UCyc t m r) Source 
(Show r, Show (t m r), Show (t m (CRTExt r))) => Show (UCyc t m r) Source 
(Tensor t, Fact m, TElt t r, CRTrans r) => Random (UCyc t m r) Source 
Arbitrary (t m r) => Arbitrary (UCyc t m r) Source 
(Tensor t, Fact m, NFData r, TElt t r, TElt t (CRTExt r)) => NFData (UCyc t m r) Source 
(UCCtx t r, Fact m) => C (UCyc t m r) Source 
(UCCtx t r, Fact m) => C (UCyc t m r) Source 
(UCCtx t r, Fact m) => C (UCyc t m r) Source 
(Reduce a b, Fact m, CElt t a, CElt t b) => Reduce (UCyc t m a) (UCyc t m b) Source 
type DecompOf (UCyc t m zq) = UCyc 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.

Basic operations

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

Same as mulG, but for UCyc.

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

Same as divG, but for UCyc.

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

Same as scalarCyc, but for UCyc.

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

Same as liftCyc, but for UCyc.

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

Same as adviseCRT, but for UCyc.

Error sampling

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

Same as tGaussian, but for UCyc.

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

Same as errorRounded, but for UCyc.

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

Same as errorCoset, but for UCyc.

Sub/extension rings

embed :: forall t r m m'. m `Divides` m' => UCyc t m r -> UCyc t m' r Source

Same as embed, but for UCyc.

twace :: forall t r m m'. (UCCtx t r, m `Divides` m') => UCyc t m' r -> UCyc t m r Source

Same as twace, but for UCyc.

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

Same as coeffsCyc, but for UCyc.

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

Same as powBasis, but for UCyc.

crtSet :: forall t m m' r p mbar m'bar. (m `Divides` m', ZPP r, p ~ CharOf (ZPOf r), mbar ~ PFree p m, m'bar ~ PFree p m', CElt t r, CElt t (ZPOf r)) => Tagged m [UCyc t m' r] Source

Same as crtSet, but for UCyc.

Representations

forceBasis :: (Fact m, CElt t r) => Maybe Basis -> UCyc t m r -> UCyc t m r Source

Yield an equivalent element whose internal representation must be in the indicated basis: powerful or decoding (for Just Pow and Just Dec arguments, respectively), or any r-basis of the implementation's choice (for Nothing argument). (See also the convenient specializations forcePow, forceDec, forceAny.)

forcePow :: (Fact m, CElt t r) => UCyc t m r -> UCyc t m r Source

Force a cyclotomic element into the powerful basis.

forceDec :: (Fact m, CElt t r) => UCyc t m r -> UCyc t m r Source

Force a cyclotomic element into the decoding basis.

forceAny :: (Fact m, CElt t r) => UCyc t m r -> UCyc t m r Source

Force a cyclotomic into any r-basis of the implementation's choice.

Specialized maps

fmapC :: (Fact m, CElt t a, CElt t b) => (a -> b) -> UCyc t m a -> UCyc t m b Source

A more specialized version of fmap: apply a function coordinate-wise in the current representation. The caller must ensure that the current representation is an r-basis (one of powerful, decoding, or CRT, if it exists), usually by using forceBasis or its specializations (forcePow, forceDec, forceAny). Otherwise, behavior is undefined.

fmapCM :: (Fact m, CElt t a, CElt t b, Monad mon) => (a -> mon b) -> UCyc t m a -> mon (UCyc t m b) Source

Monadic version of fmapC.

data Basis Source

Represents the powerful or decoding basis.

Constructors

Pow 
Dec 

Instances

class RescaleCyc c a b Source

Represents cyclotomic rings that are rescalable over their base rings. (This is a class because it allows for more efficient specialized implementations.)

Minimal complete definition

rescaleCyc

Instances

(Rescale a b, CElt t a, CElt t b) => RescaleCyc (UCyc t) a b Source 
RescaleCyc (UCyc t) a b => RescaleCyc (Cyc t) a b Source 
(Mod a, Field b, Lift a z, Reduce z b, CElt t a, CElt t b, CElt t (a, b), CElt t z) => RescaleCyc (UCyc t) (a, b) b Source