(Reflects q r, RealField r) => Reduce r (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
TensorPowDec t (RRq q r) => UnCyc t (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
TensorPowDec t (RRq q r) => ExtensionCyc (Cyc t) (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(Protoable (IZipVector m (RRq q Double)), ProtoType (IZipVector m (RRq q Double)) ~ KqProduct, Protoable (IZipVector m b), ProtoType (IZipVector m b) ~ KqProduct) => Protoable (IZipVector m (RRq q Double, b)) Source # | |
Instance detailsDefined in Crypto.Lol.Types.IZipVector |
(Fact m, Reflects q Double) => Protoable (IZipVector m (RRq q Double)) Source # | |
Instance detailsDefined in Crypto.Lol.Types.IZipVector |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(Fact m, TensorPowDec t (RRq q r), Foldable (t m)) => FoldableCyc (Cyc t m) (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(Fact m, Functor (t m), UnCyc t (RRq q r)) => FunctorCyc (Cyc t m) (RRq q r) Integer Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
Eq r => Eq (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
Show r => Show (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
Show (t m (RRq q r)) => Show (Cyc t m (RRq q r)) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
Random (RRq q Double) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
Random (t m (RRq q r)) => Random (Cyc t m (RRq q r)) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
NFData r => NFData (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
(Fact m, forall (m' :: Factored). Fact m' => NFData (t m' (RRq q r))) => NFData (Cyc t m (RRq q r)) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
C r => C (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
ZeroTestable (t m (RRq q r)) => C (Cyc t m (RRq q r)) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
RealField r => C (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
(Additive (RRq q r), TensorPowDec t (RRq q r), IFunctor t, Fact m) => C (Cyc t m (RRq q r)) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(Reflects q r, Field r, Reduce r (RRq q r)) => Lift' (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
(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 detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(Additive (RRq q r), Additive (RRq p r)) => Rescale (RRq q r) (RRq p r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
(Reflects q Double, FunctorCyc (Cyc t m) Double (RRq q Double)) => Reduce (Cyc t m Double) (Cyc t m (RRq q Double)) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
(ToInteger z, RealField r, Reflects q z, Reflects q r) => Subgroup (ZqBasic q z) (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
data Cyc t m (RRq q r) Source # | additive group \( K/qR \), limited to powerful- or decoding-basis
representation |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |
type ProtoType (IZipVector m (RRq q Double, b)) Source # | |
Instance detailsDefined in Crypto.Lol.Types.IZipVector |
type ProtoType (IZipVector m (RRq q Double)) Source # | |
Instance detailsDefined in Crypto.Lol.Types.IZipVector |
type LiftOf (RRq q r) Source # | |
Instance detailsDefined in Crypto.Lol.Types.Unsafe.RRq |
type ProtoType (Cyc t m (RRq q Double)) Source # | |
Instance detailsDefined in Crypto.Lol.Cyclotomic.Cyc |