| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Crypto.Lol.CRTrans
Description
Classes and helper methods for the Chinese remainder transform and ring extensions.
- class Ring r => CRTrans r where
- class (Ring r, Ring (CRTExt r)) => CRTEmbed r where
- type CRTInfo r = (Int -> r, r)
- crtInfoFact :: (Fact m, CRTrans r) => TaggedT m Maybe (CRTInfo r)
- crtInfoPPow :: (PPow pp, CRTrans r) => TaggedT pp Maybe (CRTInfo r)
- crtInfoNatC :: (NatC p, CRTrans r) => TaggedT p Maybe (CRTInfo r)
- gEmbPPow :: forall pp r. (PPow pp, CRTrans r) => TaggedT pp Maybe (Int -> r)
- gEmbNatC :: (NatC p, CRTrans r) => TaggedT p Maybe (Int -> r)
- omegaPowMod :: forall r. (Mod r, Enumerable r, Ring r, Eq r) => Int -> Maybe (Int -> r)
- zqHasCRT :: (ToInteger i, PID i) => i -> i -> Bool
Documentation
class Ring r => CRTrans r where Source
A ring that (possibly) supports invertible Chinese remainder transformations of various indices.
The values of crtInfo for different indices m should be
consistent, in the sense that if omega, omega' are respectively
the values returned for m, m' where m' divides m, then it
should be the case that omega^(m/m')=omega'.
Minimal complete definition
Nothing
Methods
Instances
| CRTrans Double Source | |
| CRTrans Int Source | |
| CRTrans Int64 Source | |
| CRTrans Integer Source | |
| Transcendental a => CRTrans (Complex a) Source | |
| (CRTrans a, CRTrans b) => CRTrans (a, b) Source | |
| GFCtx k fp deg => CRTrans (GF k fp deg) Source | |
| (Reflects k q z, PID z, (~) * r (ZqBasic k q z), Mod r, Enumerable r, Show z) => CRTrans (ZqBasic k q z) Source |
class (Ring r, Ring (CRTExt r)) => CRTEmbed r where Source
A ring with a ring embedding into some ring CRTExt r that has
an invertible CRT transformation for every positive index m.
type CRTInfo r = (Int -> r, r) Source
Information that characterizes the (invertible) Chinese remainder
transformation over a ring r, namely:
- a function that returns the
ith power of somemth root of unity (for any integeri) - the multiplicative inverse of
\hat{m}inr.
gEmbPPow :: forall pp r. (PPow pp, CRTrans r) => TaggedT pp Maybe (Int -> r) Source
A function that returns the ith embedding of g_{p^e} = g_p for
i in Z*_{p^e}.
gEmbNatC :: (NatC p, CRTrans r) => TaggedT p Maybe (Int -> r) Source
A function that returns the ith embedding of g_p for i in Z*_p,
i.e., 1-omega_p^i.
omegaPowMod :: forall r. (Mod r, Enumerable r, Ring r, Eq r) => Int -> Maybe (Int -> r) Source
Default implementation of omegaPow for Mod types. The
implementation finds an integer element of maximal multiplicative
order, and raises it to the appropriate power. Therefore, the
functions returned for different values of the first argument are
consistent, i.e., omega_{m'}^(m'/m) = omega_m.