lol-0.7.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2018
Chris Peikert 2011-2018
LicenseGPL-3
Maintainerecrockett0@gmail.com
Stabilityexperimental
PortabilityPOSIX \( \def\Z{\mathbb{Z}} \) \( \def\F{\mathbb{F}} \) \( \def\Q{\mathbb{Q}} \) \( \def\Tw{\text{Tw}} \) \( \def\Tr{\text{Tr}} \) \( \def\O{\mathcal{O}} \)
Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Cyclotomic.Cyc

Contents

Description

An implementation of cyclotomic rings that hides the internal representations of ring elements (e.g., the choice of basis), and also offers more efficient storage and operations on subring elements (including elements from the base ring itself).

For an implementation that allows (and requires) the programmer to control the underlying representation, see Crypto.Lol.Cyclotomic.CycRep.

WARNING: as with all fixed-point arithmetic, the functions associated with Cyc may result in overflow (and thereby incorrect answers and potential security flaws) if the input arguments are too close to the bounds imposed by the base type. The acceptable range of inputs for each function is determined by the internal linear transforms and other operations it performs.

Synopsis

Data type

data family Cyc (t :: Factored -> * -> *) (m :: Factored) r Source #

A cyclotomic ring such as \( \Z[\zeta_m] \), \( \Z_q[\zeta_m] \), or \( \Q[\zeta_m] \): t is the Tensor type for storing coefficient tensors; m is the cyclotomic index; r is the base ring of the coefficients (e.g., \(\ \Q \), \( \Z \), \( \Z_q \)).

Instances
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 #

(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 #

(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 #

Module Double (CycG t m Double) => C Double (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(*>) :: Double -> Cyc t m Double -> Cyc t m Double #

Module Int64 (CycG t m Int64) => C Int64 (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(*>) :: Int64 -> Cyc t m Int64 -> Cyc t m Int64 #

CRTElt t Int64 => ExtensionCyc (Cyc t) Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

embed :: Divides m m' => Cyc t m Int64 -> Cyc t m' Int64 Source #

twace :: Divides m m' => Cyc t m' Int64 -> Cyc t m Int64 Source #

powBasis :: Divides m m' => Tagged m [Cyc t m' Int64] Source #

coeffsCyc :: Divides m m' => Basis -> Cyc t m' Int64 -> [Cyc t m Int64] Source #

CRTElt t Double => ExtensionCyc (Cyc t) Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

embed :: Divides m m' => Cyc t m Double -> Cyc t m' Double Source #

twace :: Divides m m' => Cyc t m' Double -> Cyc t m Double Source #

powBasis :: Divides m m' => Tagged m [Cyc t m' Double] Source #

coeffsCyc :: Divides m m' => Basis -> Cyc t m' Double -> [Cyc t m Double] Source #

(ExtensionCyc (Cyc t) a, ExtensionCyc (Cyc t) b) => ExtensionCyc (Cyc t) (a, b) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

embed :: Divides m m' => Cyc t m (a, b) -> Cyc t m' (a, b) Source #

twace :: Divides m m' => Cyc t m' (a, b) -> Cyc t m (a, b) Source #

powBasis :: Divides m m' => Tagged m [Cyc t m' (a, b)] Source #

coeffsCyc :: Divides m m' => Basis -> Cyc t m' (a, b) -> [Cyc t m (a, b)] Source #

CRTSetCyc (CycG t) (ZqBasic q z) => CRTSetCyc (Cyc t) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

crtSet :: Divides m m' => Tagged m [Cyc t m' (ZqBasic q z)] Source #

TensorPowDec t (RRq q r) => ExtensionCyc (Cyc t) (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

embed :: Divides m m' => Cyc t m (RRq q r) -> Cyc t m' (RRq q r) Source #

twace :: Divides m m' => Cyc t m' (RRq q r) -> Cyc t m (RRq q r) Source #

powBasis :: Divides m m' => Tagged m [Cyc t m' (RRq q r)] Source #

coeffsCyc :: Divides m m' => Basis -> Cyc t m' (RRq q r) -> [Cyc t m (RRq q r)] Source #

ExtensionCyc (CycG t) (ZqBasic q z) => ExtensionCyc (Cyc t) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

embed :: Divides m m' => Cyc t m (ZqBasic q z) -> Cyc t m' (ZqBasic q z) Source #

twace :: Divides m m' => Cyc t m' (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

powBasis :: Divides m m' => Tagged m [Cyc t m' (ZqBasic q z)] Source #

coeffsCyc :: Divides m m' => Basis -> Cyc t m' (ZqBasic q z) -> [Cyc t m (ZqBasic q z)] Source #

Foldable (t m) => FoldableCyc (Cyc t m) Integer Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

foldrCyc :: Maybe Basis -> (Integer -> b -> b) -> b -> Cyc t m Integer -> b Source #

FoldableCyc (CycG t m) Int64 => FoldableCyc (Cyc t m) Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

foldrCyc :: Maybe Basis -> (Int64 -> b -> b) -> b -> Cyc t m Int64 -> b Source #

FoldableCyc (CycG t m) Double => FoldableCyc (Cyc t m) Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

foldrCyc :: Maybe Basis -> (Double -> b -> b) -> b -> Cyc t m Double -> b Source #

(Fact m, TensorGSqNorm t Int64, CRTElt t Int64) => GSqNormCyc (Cyc t m) Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

gSqNorm :: Cyc t m Int64 -> Int64 Source #

(Fact m, TensorGSqNorm t Double, CRTElt t Double) => GSqNormCyc (Cyc t m) Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

gSqNorm :: Cyc t m Double -> Double Source #

Functor (t m) => FunctorCyc (Cyc t m) Integer Integer Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Integer -> Integer) -> Cyc t m Integer -> Cyc t m Integer Source #

(Fact m, UnCyc t Int64, UnCyc t Int64, IFunctor t, IFElt t Int64, IFElt t Int64) => FunctorCyc (Cyc t m) Int64 Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Int64 -> Int64) -> Cyc t m Int64 -> Cyc t m Int64 Source #

(Fact m, UnCyc t Int64, UnCyc t Double, IFunctor t, IFElt t Int64, IFElt t Double) => FunctorCyc (Cyc t m) Int64 Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Int64 -> Double) -> Cyc t m Int64 -> Cyc t m Double Source #

(Fact m, UnCyc t Double, UnCyc t Int64, IFunctor t, IFElt t Double, IFElt t Int64) => FunctorCyc (Cyc t m) Double Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Double -> Int64) -> Cyc t m Double -> Cyc t m Int64 Source #

(Fact m, UnCyc t Double, UnCyc t Double, IFunctor t, IFElt t Double, IFElt t Double) => FunctorCyc (Cyc t m) Double Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Double -> Double) -> Cyc t m Double -> Cyc t m Double Source #

(Fact m, Functor (t m), UnCyc t Int64) => FunctorCyc (Cyc t m) Int64 Integer Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Int64 -> Integer) -> Cyc t m Int64 -> Cyc t m Integer Source #

(Fact m, Functor (t m), UnCyc t Double) => FunctorCyc (Cyc t m) Double Integer Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Double -> Integer) -> Cyc t m Double -> Cyc t m Integer Source #

(Fact m, Reflects q z, Reduce z b, ZeroTestable z, CRTElt t (ZqBasic q z), C b (Cyc t m b)) => RescaleCyc (Cyc t m) b (ZqBasic q z, b) Source #

rescale up by one additional modulus

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m b -> Cyc t m (ZqBasic q z, b) Source #

(Fact m, UnCyc t Int64, UnCyc t (a, b), IFunctor t, IFElt t Int64, IFElt t (a, b)) => FunctorCyc (Cyc t m) Int64 (a, b) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Int64 -> (a, b)) -> Cyc t m Int64 -> Cyc t m (a, b) Source #

(Fact m, UnCyc t Double, UnCyc t (a, b), IFunctor t, IFElt t Double, IFElt t (a, b)) => FunctorCyc (Cyc t m) Double (a, b) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Double -> (a, b)) -> Cyc t m Double -> Cyc t m (a, b) Source #

(Fact m, UnCyc t Int64, UnCyc t (ZqBasic q z), IFunctor t, IFElt t Int64, IFElt t (ZqBasic q z)) => FunctorCyc (Cyc t m) Int64 (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Int64 -> ZqBasic q z) -> Cyc t m Int64 -> Cyc t m (ZqBasic q z) Source #

(Fact m, UnCyc t Int64, UnCyc t (RRq q r), IFunctor t, IFElt t Int64, IFElt t (RRq q r)) => FunctorCyc (Cyc t m) Int64 (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Int64 -> RRq q r) -> Cyc t m Int64 -> Cyc t m (RRq q r) Source #

(Fact m, UnCyc t Double, UnCyc t (ZqBasic q z), IFunctor t, IFElt t Double, IFElt t (ZqBasic q z)) => FunctorCyc (Cyc t m) Double (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Double -> ZqBasic q z) -> Cyc t m Double -> Cyc t m (ZqBasic q z) Source #

(Fact m, UnCyc t Double, UnCyc t (RRq q r), IFunctor t, IFElt t Double, IFElt t (RRq q r)) => FunctorCyc (Cyc t m) Double (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (Double -> RRq q r) -> Cyc t m Double -> Cyc t m (RRq q r) Source #

(RescaleCyc (Cyc t m) (b, (c, (d, e))) e, RescaleCyc (Cyc t m) (a, (b, (c, (d, e)))) (b, (c, (d, e)))) => RescaleCyc (Cyc t m) (a, (b, (c, (d, e)))) e Source #

convenient rescale-down by multiple components at once

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m (a, (b, (c, (d, e)))) -> Cyc t m e Source #

(RescaleCyc (Cyc t m) (b, (c, d)) d, RescaleCyc (Cyc t m) (a, (b, (c, d))) (b, (c, d))) => RescaleCyc (Cyc t m) (a, (b, (c, d))) d Source #

convenient rescale-down by multiple components at once

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m (a, (b, (c, d))) -> Cyc t m d Source #

(RescaleCyc (Cyc t m) (b, c) c, RescaleCyc (Cyc t m) (a, (b, c)) (b, c)) => RescaleCyc (Cyc t m) (a, (b, c)) c Source #

convenient rescale-down by multiple components at once

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m (a, (b, c)) -> Cyc t m c Source #

(ToInteger z, Reflects q z, Reduce z b, Field b, FunctorCyc (Cyc t m) (ZqBasic q z) z, FunctorCyc (Cyc t m) z b, Additive (Cyc t m b), Module b (Cyc t m b)) => RescaleCyc (Cyc t m) (ZqBasic q z, b) b Source #

specialized (faster) rescale-down by a single \(\Z_q\)

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m (ZqBasic q z, b) -> Cyc t m b Source #

(Fact m, UnCyc t (a, b), UnCyc t Int64, IFunctor t, IFElt t (a, b), IFElt t Int64) => FunctorCyc (Cyc t m) (a, b) Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> ((a, b) -> Int64) -> Cyc t m (a, b) -> Cyc t m Int64 Source #

(Fact m, UnCyc t (a, b), UnCyc t Double, IFunctor t, IFElt t (a, b), IFElt t Double) => FunctorCyc (Cyc t m) (a, b) Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> ((a, b) -> Double) -> Cyc t m (a, b) -> Cyc t m Double Source #

(Fact m, Functor (t m), UnCyc t (a, b)) => FunctorCyc (Cyc t m) (a, b) Integer Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> ((a, b) -> Integer) -> Cyc t m (a, b) -> Cyc t m Integer Source #

RescaleCyc (Cyc t m) (a, b) (a, b) Source #

no-op rescale for Cyc over pairs

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m (a, b) -> Cyc t m (a, b) Source #

(Fact m, UnCyc t (a, b), UnCyc t (a, b), IFunctor t, IFElt t (a, b), IFElt t (a, b)) => FunctorCyc (Cyc t m) (a, b) (a, b) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> ((a, b) -> (a, b)) -> Cyc t m (a, b) -> Cyc t m (a, b) Source #

(Fact m, UnCyc t (a, b), UnCyc t (ZqBasic q z), IFunctor t, IFElt t (a, b), IFElt t (ZqBasic q z)) => FunctorCyc (Cyc t m) (a, b) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> ((a, b) -> ZqBasic q z) -> Cyc t m (a, b) -> Cyc t m (ZqBasic q z) Source #

(Fact m, UnCyc t (a, b), UnCyc t (RRq q r), IFunctor t, IFElt t (a, b), IFElt t (RRq q r)) => FunctorCyc (Cyc t m) (a, b) (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> ((a, b) -> RRq q r) -> Cyc t m (a, b) -> Cyc t m (RRq q r) Source #

(Module a (Cyc t m a), Module b (Cyc t m b)) => C (a, b) (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(*>) :: (a, b) -> Cyc t m (a, b) -> Cyc t m (a, b) #

(Fact m, TensorPowDec t (RRq q r), Foldable (t m)) => FoldableCyc (Cyc t m) (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

foldrCyc :: Maybe Basis -> (RRq q r -> b -> b) -> b -> Cyc t m (RRq q r) -> b Source #

FoldableCyc (CycG t m) (ZqBasic q z) => FoldableCyc (Cyc t m) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

foldrCyc :: Maybe Basis -> (ZqBasic q z -> b -> b) -> b -> Cyc t m (ZqBasic q z) -> b Source #

(Fact m, UnCyc t (ZqBasic q z), UnCyc t Int64, IFunctor t, IFElt t (ZqBasic q z), IFElt t Int64) => FunctorCyc (Cyc t m) (ZqBasic q z) Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (ZqBasic q z -> Int64) -> Cyc t m (ZqBasic q z) -> Cyc t m Int64 Source #

(Fact m, UnCyc t (ZqBasic q z), UnCyc t Double, IFunctor t, IFElt t (ZqBasic q z), IFElt t Double) => FunctorCyc (Cyc t m) (ZqBasic q z) Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (ZqBasic q z -> Double) -> Cyc t m (ZqBasic q z) -> Cyc t m Double Source #

(Fact m, UnCyc t (RRq q r), UnCyc t Int64, IFunctor t, IFElt t (RRq q r), IFElt t Int64) => FunctorCyc (Cyc t m) (RRq q r) Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (RRq q r -> Int64) -> Cyc t m (RRq q r) -> Cyc t m Int64 Source #

(Fact m, UnCyc t (RRq q r), UnCyc t Double, IFunctor t, IFElt t (RRq q r), IFElt t Double) => FunctorCyc (Cyc t m) (RRq q r) Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (RRq q r -> Double) -> Cyc t m (RRq q r) -> Cyc t m Double Source #

(Fact m, Functor (t m), UnCyc t (ZqBasic q z)) => FunctorCyc (Cyc t m) (ZqBasic q z) Integer Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (ZqBasic q z -> Integer) -> Cyc t m (ZqBasic q z) -> Cyc t m Integer Source #

(Fact m, Functor (t m), UnCyc t (RRq q r)) => FunctorCyc (Cyc t m) (RRq q r) Integer Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (RRq q r -> Integer) -> Cyc t m (RRq q r) -> Cyc t m Integer Source #

(Fact m, UnCyc t (ZqBasic q z), UnCyc t (a, b), IFunctor t, IFElt t (ZqBasic q z), IFElt t (a, b)) => FunctorCyc (Cyc t m) (ZqBasic q z) (a, b) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (ZqBasic q z -> (a, b)) -> Cyc t m (ZqBasic q z) -> Cyc t m (a, b) Source #

(Fact m, UnCyc t (RRq q r), UnCyc t (a, b), IFunctor t, IFElt t (RRq q r), IFElt t (a, b)) => FunctorCyc (Cyc t m) (RRq q r) (a, b) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (RRq q r -> (a, b)) -> Cyc t m (RRq q r) -> Cyc t m (a, b) Source #

(Fact m, Rescale (RRq q r) (RRq p r), TensorPowDec t (RRq q r), TensorPowDec t (RRq p r)) => RescaleCyc (Cyc t m) (RRq q r) (RRq p r) Source #

rescale from one modulus to another

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m (RRq q r) -> Cyc t m (RRq p r) Source #

RescaleCyc (CycG t m) (ZqBasic q z) (ZqBasic p z) => RescaleCyc (Cyc t m) (ZqBasic q z) (ZqBasic p z) Source #

rescale from one modulus to another

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescaleCyc :: Basis -> Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic p z) Source #

(Fact m, UnCyc t (ZqBasic q z), UnCyc t (ZqBasic q z), IFunctor t, IFElt t (ZqBasic q z), IFElt t (ZqBasic q z)) => FunctorCyc (Cyc t m) (ZqBasic q z) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (ZqBasic q z -> ZqBasic q z) -> Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

(Fact m, UnCyc t (ZqBasic q z), UnCyc t (RRq q r), IFunctor t, IFElt t (ZqBasic q z), IFElt t (RRq q r)) => FunctorCyc (Cyc t m) (ZqBasic q z) (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (ZqBasic q z -> RRq q r) -> Cyc t m (ZqBasic q z) -> Cyc t m (RRq q r) Source #

(Fact m, UnCyc t (RRq q r), UnCyc t (ZqBasic q z), IFunctor t, IFElt t (RRq q r), IFElt t (ZqBasic q z)) => FunctorCyc (Cyc t m) (RRq q r) (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (RRq q r -> ZqBasic q z) -> Cyc t m (RRq q r) -> Cyc t m (ZqBasic q z) Source #

(Fact m, UnCyc t (RRq q r), UnCyc t (RRq q r), IFunctor t, IFElt t (RRq q r), IFElt t (RRq q r)) => FunctorCyc (Cyc t m) (RRq q r) (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

fmapCyc :: Maybe Basis -> (RRq q r -> RRq q r) -> Cyc t m (RRq q r) -> Cyc t m (RRq q r) Source #

(Eq (Cyc t m a), Eq (Cyc t m b)) => Eq (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(==) :: Cyc t m (a, b) -> Cyc t m (a, b) -> Bool #

(/=) :: Cyc t m (a, b) -> Cyc t m (a, b) -> Bool #

Eq (CycG t m (ZqBasic q z)) => Eq (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(==) :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) -> Bool #

(/=) :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) -> Bool #

Eq (CycG t m Int64) => Eq (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(==) :: Cyc t m Int64 -> Cyc t m Int64 -> Bool #

(/=) :: Cyc t m Int64 -> Cyc t m Int64 -> Bool #

Show (t m (RRq q r)) => Show (Cyc t m (RRq q r)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

showsPrec :: Int -> Cyc t m (RRq q r) -> ShowS #

show :: Cyc t m (RRq q r) -> String #

showList :: [Cyc t m (RRq q r)] -> ShowS #

Show (t m Integer) => Show (Cyc t m Integer) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

showsPrec :: Int -> Cyc t m Integer -> ShowS #

show :: Cyc t m Integer -> String #

showList :: [Cyc t m Integer] -> ShowS #

(Show (Cyc t m a), Show (Cyc t m b)) => Show (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

showsPrec :: Int -> Cyc t m (a, b) -> ShowS #

show :: Cyc t m (a, b) -> String #

showList :: [Cyc t m (a, b)] -> ShowS #

Show (CycG t m (ZqBasic q z)) => Show (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

showsPrec :: Int -> Cyc t m (ZqBasic q z) -> ShowS #

show :: Cyc t m (ZqBasic q z) -> String #

showList :: [Cyc t m (ZqBasic q z)] -> ShowS #

Show (CycG t m Int64) => Show (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

showsPrec :: Int -> Cyc t m Int64 -> ShowS #

show :: Cyc t m Int64 -> String #

showList :: [Cyc t m Int64] -> ShowS #

Show (CycG t m Double) => Show (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

showsPrec :: Int -> Cyc t m Double -> ShowS #

show :: Cyc t m Double -> String #

showList :: [Cyc t m Double] -> ShowS #

Random (t m (RRq q r)) => Random (Cyc t m (RRq q r)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

randomR :: RandomGen g => (Cyc t m (RRq q r), Cyc t m (RRq q r)) -> g -> (Cyc t m (RRq q r), g) #

random :: RandomGen g => g -> (Cyc t m (RRq q r), g) #

randomRs :: RandomGen g => (Cyc t m (RRq q r), Cyc t m (RRq q r)) -> g -> [Cyc t m (RRq q r)] #

randoms :: RandomGen g => g -> [Cyc t m (RRq q r)] #

randomRIO :: (Cyc t m (RRq q r), Cyc t m (RRq q r)) -> IO (Cyc t m (RRq q r)) #

randomIO :: IO (Cyc t m (RRq q r)) #

(Random (t m Integer), Fact m) => Random (Cyc t m Integer) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

randomR :: RandomGen g => (Cyc t m Integer, Cyc t m Integer) -> g -> (Cyc t m Integer, g) #

random :: RandomGen g => g -> (Cyc t m Integer, g) #

randomRs :: RandomGen g => (Cyc t m Integer, Cyc t m Integer) -> g -> [Cyc t m Integer] #

randoms :: RandomGen g => g -> [Cyc t m Integer] #

randomRIO :: (Cyc t m Integer, Cyc t m Integer) -> IO (Cyc t m Integer) #

randomIO :: IO (Cyc t m Integer) #

(Random (Cyc t m a), Random (Cyc t m b)) => Random (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

randomR :: RandomGen g => (Cyc t m (a, b), Cyc t m (a, b)) -> g -> (Cyc t m (a, b), g) #

random :: RandomGen g => g -> (Cyc t m (a, b), g) #

randomRs :: RandomGen g => (Cyc t m (a, b), Cyc t m (a, b)) -> g -> [Cyc t m (a, b)] #

randoms :: RandomGen g => g -> [Cyc t m (a, b)] #

randomRIO :: (Cyc t m (a, b), Cyc t m (a, b)) -> IO (Cyc t m (a, b)) #

randomIO :: IO (Cyc t m (a, b)) #

Random (CycG t m (ZqBasic q z)) => Random (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

randomR :: RandomGen g => (Cyc t m (ZqBasic q z), Cyc t m (ZqBasic q z)) -> g -> (Cyc t m (ZqBasic q z), g) #

random :: RandomGen g => g -> (Cyc t m (ZqBasic q z), g) #

randomRs :: RandomGen g => (Cyc t m (ZqBasic q z), Cyc t m (ZqBasic q z)) -> g -> [Cyc t m (ZqBasic q z)] #

randoms :: RandomGen g => g -> [Cyc t m (ZqBasic q z)] #

randomRIO :: (Cyc t m (ZqBasic q z), Cyc t m (ZqBasic q z)) -> IO (Cyc t m (ZqBasic q z)) #

randomIO :: IO (Cyc t m (ZqBasic q z)) #

Random (CycG t m Int64) => Random (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

randomR :: RandomGen g => (Cyc t m Int64, Cyc t m Int64) -> g -> (Cyc t m Int64, g) #

random :: RandomGen g => g -> (Cyc t m Int64, g) #

randomRs :: RandomGen g => (Cyc t m Int64, Cyc t m Int64) -> g -> [Cyc t m Int64] #

randoms :: RandomGen g => g -> [Cyc t m Int64] #

randomRIO :: (Cyc t m Int64, Cyc t m Int64) -> IO (Cyc t m Int64) #

randomIO :: IO (Cyc t m Int64) #

Random (CycG t m Double) => Random (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

randomR :: RandomGen g => (Cyc t m Double, Cyc t m Double) -> g -> (Cyc t m Double, g) #

random :: RandomGen g => g -> (Cyc t m Double, g) #

randomRs :: RandomGen g => (Cyc t m Double, Cyc t m Double) -> g -> [Cyc t m Double] #

randoms :: RandomGen g => g -> [Cyc t m Double] #

randomRIO :: (Cyc t m Double, Cyc t m Double) -> IO (Cyc t m Double) #

randomIO :: IO (Cyc t m Double) #

(Fact m, forall (m' :: Factored). Fact m' => NFData (t m' (RRq q r))) => NFData (Cyc t m (RRq q r)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rnf :: Cyc t m (RRq q r) -> () #

(Fact m, forall (m' :: Factored). Fact m' => NFData (t m' Integer)) => NFData (Cyc t m Integer) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rnf :: Cyc t m Integer -> () #

(NFData (Cyc t m a), NFData (Cyc t m b)) => NFData (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rnf :: Cyc t m (a, b) -> () #

NFData (CycG t m (ZqBasic q z)) => NFData (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rnf :: Cyc t m (ZqBasic q z) -> () #

NFData (CycG t m Int64) => NFData (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rnf :: Cyc t m Int64 -> () #

NFData (CycG t m Double) => NFData (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rnf :: Cyc t m Double -> () #

(Ring (Cyc t m a), Ring (Cyc t m b)) => C (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(*) :: Cyc t m (a, b) -> Cyc t m (a, b) -> Cyc t m (a, b) #

one :: Cyc t m (a, b) #

fromInteger :: Integer -> Cyc t m (a, b) #

(^) :: Cyc t m (a, b) -> Integer -> Cyc t m (a, b) #

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

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

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

one :: Cyc t m (ZqBasic q z) #

fromInteger :: Integer -> Cyc t m (ZqBasic q z) #

(^) :: Cyc t m (ZqBasic q z) -> Integer -> Cyc t m (ZqBasic q z) #

Ring (CycG t m Int64) => C (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(*) :: Cyc t m Int64 -> Cyc t m Int64 -> Cyc t m Int64 #

one :: Cyc t m Int64 #

fromInteger :: Integer -> Cyc t m Int64 #

(^) :: Cyc t m Int64 -> Integer -> Cyc t m Int64 #

Ring (CycG t m Double) => C (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

(*) :: Cyc t m Double -> Cyc t m Double -> Cyc t m Double #

one :: Cyc t m Double #

fromInteger :: Integer -> Cyc t m Double #

(^) :: Cyc t m Double -> Integer -> Cyc t m Double #

ZeroTestable (t m (RRq q r)) => C (Cyc t m (RRq q r)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

isZero :: Cyc t m (RRq q r) -> Bool #

ZeroTestable (t m Integer) => C (Cyc t m Integer) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

isZero :: Cyc t m Integer -> Bool #

(ZeroTestable (Cyc t m a), ZeroTestable (Cyc t m b)) => C (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

isZero :: Cyc t m (a, b) -> Bool #

ZeroTestable (CycG t m (ZqBasic q z)) => C (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

isZero :: Cyc t m (ZqBasic q z) -> Bool #

ZeroTestable (CycG t m Int64) => C (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

isZero :: Cyc t m Int64 -> Bool #

ZeroTestable (CycG t m Double) => C (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

isZero :: Cyc t m Double -> Bool #

(Additive (RRq q r), TensorPowDec t (RRq q r), IFunctor t, Fact m) => C (Cyc t m (RRq q r)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

zero :: Cyc t m (RRq q r) #

(+) :: Cyc t m (RRq q r) -> Cyc t m (RRq q r) -> Cyc t m (RRq q r) #

(-) :: Cyc t m (RRq q r) -> Cyc t m (RRq q r) -> Cyc t m (RRq q r) #

negate :: Cyc t m (RRq q r) -> Cyc t m (RRq q r) #

(Additive (Cyc t m a), Additive (Cyc t m b)) => C (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

zero :: Cyc t m (a, b) #

(+) :: Cyc t m (a, b) -> Cyc t m (a, b) -> Cyc t m (a, b) #

(-) :: Cyc t m (a, b) -> Cyc t m (a, b) -> Cyc t m (a, b) #

negate :: Cyc t m (a, b) -> Cyc t m (a, b) #

Additive (CycG t m (ZqBasic q z)) => C (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

zero :: Cyc t m (ZqBasic q z) #

(+) :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) #

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

negate :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) #

Additive (CycG t m Int64) => C (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

zero :: Cyc t m Int64 #

(+) :: Cyc t m Int64 -> Cyc t m Int64 -> Cyc t m Int64 #

(-) :: Cyc t m Int64 -> Cyc t m Int64 -> Cyc t m Int64 #

negate :: Cyc t m Int64 -> Cyc t m Int64 #

Additive (CycG t m Double) => C (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

zero :: Cyc t m Double #

(+) :: Cyc t m Double -> Cyc t m Double -> Cyc t m Double #

(-) :: Cyc t m Double -> Cyc t m Double -> Cyc t m Double #

negate :: Cyc t m Double -> Cyc t m Double #

(Lift' r, FunctorCyc (Cyc t m) r (LiftOf r)) => LiftCyc (Cyc t m r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

liftCyc :: Maybe Basis -> Cyc t m r -> LiftOf (Cyc t m r) Source #

CosetGaussianCyc (CycG t m (ZqBasic q Int64)) => CosetGaussianCyc (Cyc t m (ZqBasic q Int64)) Source #

uses Double for the intermediate Gaussian samples

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

cosetGaussian :: (ToRational v, MonadRandom rnd) => v -> Cyc t m (ZqBasic q Int64) -> rnd (LiftOf (Cyc t m (ZqBasic q Int64))) Source #

(Fact m, TensorGaussian t Double, FunctorCyc (Cyc t m) Double Int64) => RoundedGaussianCyc (Cyc t m Int64) Source #

uses Double for the intermediate Gaussian sample

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

roundedGaussian :: (ToRational v, MonadRandom rnd) => v -> rnd (Cyc t m Int64) Source #

(Fact m, TensorGaussian t Double) => GaussianCyc (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

tweakedGaussian :: (ToRational v, MonadRandom rnd) => v -> rnd (Cyc t m Double) Source #

(Cyclotomic (Cyc t m a), Cyclotomic (Cyc t m b)) => Cyclotomic (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

mulG :: Cyc t m (a, b) -> Cyc t m (a, b) Source #

divG :: Cyc t m (a, b) -> Maybe (Cyc t m (a, b)) Source #

advisePow :: Cyc t m (a, b) -> Cyc t m (a, b) Source #

adviseDec :: Cyc t m (a, b) -> Cyc t m (a, b) Source #

adviseCRT :: Cyc t m (a, b) -> Cyc t m (a, b) Source #

Cyclotomic (CycG t m (ZqBasic q z)) => Cyclotomic (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

mulG :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

divG :: Cyc t m (ZqBasic q z) -> Maybe (Cyc t m (ZqBasic q z)) Source #

advisePow :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

adviseDec :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

adviseCRT :: Cyc t m (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

Cyclotomic (CycG t m Int64) => Cyclotomic (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

mulG :: Cyc t m Int64 -> Cyc t m Int64 Source #

divG :: Cyc t m Int64 -> Maybe (Cyc t m Int64) Source #

advisePow :: Cyc t m Int64 -> Cyc t m Int64 Source #

adviseDec :: Cyc t m Int64 -> Cyc t m Int64 Source #

adviseCRT :: Cyc t m Int64 -> Cyc t m Int64 Source #

Cyclotomic (CycG t m Double) => Cyclotomic (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

mulG :: Cyc t m Double -> Cyc t m Double Source #

divG :: Cyc t m Double -> Maybe (Cyc t m Double) Source #

advisePow :: Cyc t m Double -> Cyc t m Double Source #

adviseDec :: Cyc t m Double -> Cyc t m Double Source #

adviseCRT :: Cyc t m Double -> Cyc t m Double Source #

(Fact m, CRTElt t Double, TensorPowDec t (RRq q Double), Protoable (CycRep t D m (RRq q Double))) => Protoable (Cyc t m (RRq q Double)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m (RRq q Double)) :: Type Source #

Methods

toProto :: Cyc t m (RRq q Double) -> ProtoType (Cyc t m (RRq q Double)) Source #

fromProto :: MonadError String m0 => ProtoType (Cyc t m (RRq q Double)) -> m0 (Cyc t m (RRq q Double)) Source #

(Fact m, CRTElt t Double, Protoable (CycG t m (ZqBasic q z))) => Protoable (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m (ZqBasic q z)) :: Type Source #

Methods

toProto :: Cyc t m (ZqBasic q z) -> ProtoType (Cyc t m (ZqBasic q z)) Source #

fromProto :: MonadError String m0 => ProtoType (Cyc t m (ZqBasic q z)) -> m0 (Cyc t m (ZqBasic q z)) Source #

(Fact m, CRTElt t Int64, Protoable (CycG t m Int64)) => Protoable (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m Int64) :: Type Source #

Methods

toProto :: Cyc t m Int64 -> ProtoType (Cyc t m Int64) Source #

fromProto :: MonadError String m0 => ProtoType (Cyc t m Int64) -> m0 (Cyc t m Int64) Source #

(Fact m, CRTElt t Double, Protoable (CycG t m Double)) => Protoable (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Associated Types

type ProtoType (Cyc t m Double) :: Type Source #

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

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

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

(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) #

(RescaleCyc (Cyc t m) a b, Fact m, Additive (Cyc t m a), Additive (Cyc t m b)) => Rescale (Cyc t m a) (Cyc t m b) Source #

Rescales relative to the powerful basis. This instance is provided for convenience, but usage of RescaleCyc is preferred to explicitly specify which basis by which to rescale.

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

rescale :: Cyc t m a -> Cyc t m b Source #

(Reduce (Cyc t m z) (Cyc t m a), Reduce (Cyc t m z) (Cyc t m b)) => Reduce (Cyc t m z) (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

reduce :: Cyc t m z -> Cyc t m (a, b) Source #

(Reflects q Double, FunctorCyc (Cyc t m) Double (RRq q Double)) => Reduce (Cyc t m Double) (Cyc t m (RRq q Double)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

reduce :: Cyc t m Double -> Cyc t m (RRq q Double) Source #

(Reflects q Int64, Functor (t m)) => Reduce (Cyc t m Integer) (Cyc t m (ZqBasic q Int64)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

reduce :: Cyc t m Integer -> Cyc t m (ZqBasic q Int64) Source #

Reduce (CycG t m Int64) (CycG t m (ZqBasic q Int64)) => Reduce (Cyc t m Int64) (Cyc t m (ZqBasic q Int64)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

reduce :: Cyc t m Int64 -> Cyc t m (ZqBasic q Int64) Source #

data Cyc t m Integer Source #

cyclotomic ring of integers with unbounded precision, limited to powerful- or decoding-basis representation.

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

data Cyc t m Integer
newtype Cyc t m Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

newtype Cyc t m Int64 = CycI64 {}
newtype Cyc t m Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

newtype Cyc t m Double = CycDbl {}
data Cyc t m (a, b) Source #

cyclotomic over a product base ring, represented as a product of cyclotomics over the individual rings

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

data Cyc t m (a, b) = CycPair !(Cyc t m a) !(Cyc t m b)
data Cyc t m (RRq q r) Source #

additive group \( K/qR \), limited to powerful- or decoding-basis representation

Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

data Cyc t m (RRq q r)
newtype Cyc t m (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

newtype Cyc t m (ZqBasic q z) = CycZqB {}
type LiftOf (Cyc t m r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

type LiftOf (Cyc t m r) = Cyc t m (LiftOf r)
type DecompOf (Cyc t m (a, b)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

type DecompOf (Cyc t m (a, b)) = DecompOf (Cyc t m a)
type DecompOf (Cyc t m (ZqBasic q Int64)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

type DecompOf (Cyc t m (ZqBasic q Int64)) = Cyc t m Int64
type ProtoType (Cyc t m (RRq q Double)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

type ProtoType (Cyc t m (RRq q Double))
type ProtoType (Cyc t m (ZqBasic q z)) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

type ProtoType (Cyc t m (ZqBasic q z))
type ProtoType (Cyc t m Int64) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

type ProtoType (Cyc t m Int64)
type ProtoType (Cyc t m Double) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

type ProtoType (Cyc t m Double)

Constructors/deconstructors

class UnCyc t r where Source #

Go between Cyc and CycRep, in a desired representation.

Methods

cycPow :: Fact m => CycRep t P m r -> Cyc t m r Source #

cycDec :: Fact m => CycRep t D m r -> Cyc t m r Source #

unCycPow :: Fact m => Cyc t m r -> CycRep t P m r Source #

unCycDec :: Fact m => Cyc t m r -> CycRep t D m r Source #

Instances
CRTElt t Int64 => UnCyc t Int64 Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

cycPow :: Fact m => CycRep t P m Int64 -> Cyc t m Int64 Source #

cycDec :: Fact m => CycRep t D m Int64 -> Cyc t m Int64 Source #

unCycPow :: Fact m => Cyc t m Int64 -> CycRep t P m Int64 Source #

unCycDec :: Fact m => Cyc t m Int64 -> CycRep t D m Int64 Source #

CRTElt t Double => UnCyc t Double Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

cycPow :: Fact m => CycRep t P m Double -> Cyc t m Double Source #

cycDec :: Fact m => CycRep t D m Double -> Cyc t m Double Source #

unCycPow :: Fact m => Cyc t m Double -> CycRep t P m Double Source #

unCycDec :: Fact m => Cyc t m Double -> CycRep t D m Double Source #

(UnCyc t a, UnCyc t b, IFunctor t, IFElt t a, IFElt t b, IFElt t (a, b)) => UnCyc t (a, b) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

cycPow :: Fact m => CycRep t P m (a, b) -> Cyc t m (a, b) Source #

cycDec :: Fact m => CycRep t D m (a, b) -> Cyc t m (a, b) Source #

unCycPow :: Fact m => Cyc t m (a, b) -> CycRep t P m (a, b) Source #

unCycDec :: Fact m => Cyc t m (a, b) -> CycRep t D m (a, b) Source #

TensorPowDec t (RRq q r) => UnCyc t (RRq q r) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

cycPow :: Fact m => CycRep t P m (RRq q r) -> Cyc t m (RRq q r) Source #

cycDec :: Fact m => CycRep t D m (RRq q r) -> Cyc t m (RRq q r) Source #

unCycPow :: Fact m => Cyc t m (RRq q r) -> CycRep t P m (RRq q r) Source #

unCycDec :: Fact m => Cyc t m (RRq q r) -> CycRep t D m (RRq q r) Source #

CRTElt t (ZqBasic q z) => UnCyc t (ZqBasic q z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Cyc

Methods

cycPow :: Fact m => CycRep t P m (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

cycDec :: Fact m => CycRep t D m (ZqBasic q z) -> Cyc t m (ZqBasic q z) Source #

unCycPow :: Fact m => Cyc t m (ZqBasic q z) -> CycRep t P m (ZqBasic q z) Source #

unCycDec :: Fact m => Cyc t m (ZqBasic q z) -> CycRep t D m (ZqBasic q z) Source #