Copyright | (c) Eric Crockett 2011-2017 Chris Peikert 2011-2017 |
---|---|
License | GPL-3 |
Maintainer | ecrockett0@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Crypto.Lol.Cyclotomic.Tensor
Description
Interface for cyclotomic tensors, and helper functions for tensor indexing.
Synopsis
- class (forall m. Fact m => (Applicative (t m), Traversable (t m)), IFunctor t, IFElt t r, Additive r) => TensorPowDec t r where
- class TensorPowDec t r => TensorG t r where
- class (TensorPowDec t r, CRTrans mon r, forall m. Fact m => C r (t m r)) => TensorCRT t mon r where
- crtFuncs :: Fact m => mon (r -> t m r, t m r -> t m r, t m r -> t m r, t m r -> t m r, t m r -> t m r)
- crtExtFuncs :: m `Divides` m' => mon (t m' r -> t m r, t m r -> t m' r)
- class TensorGaussian t q where
- tweakedGaussianDec :: (ToRational v, Fact m, MonadRandom rnd) => v -> rnd (t m q)
- class TensorGSqNorm t r where
- gSqNormDec :: Fact m => t m r -> r
- class TensorPowDec t fp => TensorCRTSet t fp where
- hasCRTFuncs :: forall t m r mon. (TensorCRT t mon r, Fact m) => mon ()
- scalarCRT :: (TensorCRT t mon r, Fact m) => mon (r -> t m r)
- mulGCRT :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r)
- divGCRT :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r)
- crt :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r)
- crtInv :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r)
- twaceCRT :: forall t m m' mon r. (TensorCRT t mon r, m `Divides` m') => mon (t m' r -> t m r)
- embedCRT :: forall t m m' mon r. (TensorCRT t mon r, m `Divides` m') => mon (t m r -> t m' r)
- data Kron r
- indexK :: Ring r => Kron r -> Int -> Int -> r
- gCRTK :: forall m mon r. (Fact m, CRTrans mon r) => mon (Kron r)
- gInvCRTK :: forall m mon r. (Fact m, CRTrans mon r) => mon (Kron r)
- twCRTs :: forall m mon r. (Fact m, CRTrans mon r) => mon (Kron r)
- zmsToIndexFact :: forall m. Fact m => Int -> Int
- indexInfo :: forall m m'. m `Divides` m' => ([(Int, Int, Int)], Int, Int, [(Int, Int)])
- extIndicesPowDec :: forall m m'. m `Divides` m' => Vector Int
- extIndicesCRT :: forall m m'. m `Divides` m' => Vector Int
- extIndicesCoeffs :: forall m m'. m `Divides` m' => Vector (Vector Int)
- baseIndicesPow :: forall m m'. m `Divides` m' => Vector (Int, Int)
- baseIndicesDec :: forall m m'. m `Divides` m' => Vector (Maybe (Int, Bool))
- baseIndicesCRT :: forall m m'. m `Divides` m' => Vector Int
- digitRev :: PP -> Int -> Int
Documentation
class (forall m. Fact m => (Applicative (t m), Traversable (t m)), IFunctor t, IFElt t r, Additive r) => TensorPowDec t r where Source #
Encapsulates linear transformations needed for cyclotomic ring arithmetic.
The type t m r
represents a cyclotomic coefficient tensor of
index m over base ring r. Most of the methods represent linear
transforms corresponding to operations in particular bases.
CRT-related methods are wrapped in Maybe
because they are
well-defined only when a CRT basis exists over the ring r for
index m.
WARNING: as with all fixed-point arithmetic, the methods
in TensorPowDec
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 method is determined by the linear transform it
implements.
Methods
scalarPow :: Fact m => r -> t m r Source #
Convert a scalar to a tensor in the powerful basis.
powToDec :: Fact m => t m r -> t m r Source #
Convert between the decoding-basis and powerful-basis representations.
decToPow :: Fact m => t m r -> t m r Source #
Convert between the decoding-basis and powerful-basis representations.
twacePowDec :: m `Divides` m' => t m' r -> t m r Source #
The twace
linear transformation, which is the same in both the
powerful and decoding bases.
embedPow :: m `Divides` m' => t m r -> t m' r Source #
The embed
linear transformations, for the powerful and
decoding bases.
embedDec :: m `Divides` m' => t m r -> t m' r Source #
The embed
linear transformations, for the powerful and
decoding bases.
coeffs :: m `Divides` m' => t m' r -> [t m r] Source #
Map a tensor in the powerfuldecodingCRT basis, representing an Om′ element, to a vector of tensors representing Om elements in the same kind of basis.
powBasisPow :: m `Divides` m' => Tagged m [t m' r] Source #
The relative powerful basis of Om′/Om, w.r.t. the powerful basis of Om′.
class TensorPowDec t r => TensorG t r where Source #
Encapsulates multiplication and division by gm
Methods
mulGPow :: Fact m => t m r -> t m r Source #
Multiply by gm in the powerful/decoding basis
mulGDec :: Fact m => t m r -> t m r Source #
Multiply by gm in the powerful/decoding basis
divGPow :: Fact m => t m r -> Maybe (t m r) Source #
Divide by gm in the powerful/decoding basis. The Maybe
output indicates that the operation may fail, which happens
exactly when the input is not divisible by gm.
divGDec :: Fact m => t m r -> Maybe (t m r) Source #
Divide by gm in the powerful/decoding basis. The Maybe
output indicates that the operation may fail, which happens
exactly when the input is not divisible by gm.
class (TensorPowDec t r, CRTrans mon r, forall m. Fact m => C r (t m r)) => TensorCRT t mon r where Source #
Encapsulates functions related to the Chinese-remainder representation/transform.
Methods
crtFuncs :: Fact m => mon (r -> t m r, t m r -> t m r, t m r -> t m r, t m r -> t m r, t m r -> t m r) Source #
A tuple of all the operations relating to the CRT basis, in a
single Maybe
value for safety. Clients should typically not
use this method directly, but instead call the corresponding
top-level functions: the elements of the tuple correpond to the
functions scalarCRT
, mulGCRT
, divGCRT
, crt
, crtInv
.
crtExtFuncs :: m `Divides` m' => mon (t m' r -> t m r, t m r -> t m' r) Source #
class TensorGaussian t q where Source #
A coefficient tensor that supports Gaussian sampling.
Methods
tweakedGaussianDec :: (ToRational v, Fact m, MonadRandom rnd) => v -> rnd (t m q) Source #
Sample from the "tweaked" Gaussian error distribution t⋅D in the decoding basis, where D has scaled variance v.
class TensorGSqNorm t r where Source #
A coefficient tensor that supports taking norms under the canonical embedding.
Methods
gSqNormDec :: Fact m => t m r -> r Source #
Given the coefficient tensor of e with respect to the decoding basis of R, yield the (scaled) squared norm of gm⋅e under the canonical embedding, namely, ˆm−1⋅‖.
class TensorPowDec t fp => TensorCRTSet t fp where Source #
A TensorPowDec
that supports relative CRT sets for the element type
fp
representing a prime-order finite field.
Top-level CRT functions
hasCRTFuncs :: forall t m r mon. (TensorCRT t mon r, Fact m) => mon () Source #
Convenience value indicating whether crtFuncs
exists.
scalarCRT :: (TensorCRT t mon r, Fact m) => mon (r -> t m r) Source #
Yield a tensor for a scalar in the CRT basis. (This function is
simply an appropriate entry from crtFuncs
.)
mulGCRT :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r) Source #
Multiply by g_m in the CRT basis. (This function is simply an
appropriate entry from crtFuncs
.)
divGCRT :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r) Source #
Divide by g_m in the CRT basis. (This function is simply an
appropriate entry from crtFuncs
.)
crt :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r) Source #
The CRT transform. (This function is simply an appropriate entry
from crtFuncs
.)
crtInv :: (TensorCRT t mon r, Fact m) => mon (t m r -> t m r) Source #
The inverse CRT transform. (This function is simply an
appropriate entry from crtFuncs
.)
twaceCRT :: forall t m m' mon r. (TensorCRT t mon r, m `Divides` m') => mon (t m' r -> t m r) Source #
The "tweaked trace" function for tensors in the CRT basis:
For cyclotomic indices m \mid m',
\Tw(x) = (\hat{m}/\hat{m}') \cdot \Tr((g'/g) \cdot x).
(This function is simply an appropriate entry from crtExtFuncs
.)
embedCRT :: forall t m m' mon r. (TensorCRT t mon r, m `Divides` m') => mon (t m r -> t m' r) Source #
Embed a tensor with index m in the CRT basis to a tensor with
index m' in the CRT basis.
(This function is simply an appropriate entry from crtExtFuncs
.)
Special vectors/matrices
gCRTK :: forall m mon r. (Fact m, CRTrans mon r) => mon (Kron r) Source #
A \varphi(m)-by-1 matrix of the CRT coefficients of g_m, for mth cyclotomic.
gInvCRTK :: forall m mon r. (Fact m, CRTrans mon r) => mon (Kron r) Source #
A \varphi(m)-by-1 matrix of the inverse CRT coefficients of g_m, for mth cyclotomic.
twCRTs :: forall m mon r. (Fact m, CRTrans mon r) => mon (Kron r) Source #
The "tweaked" \CRT^* matrix: \CRT^* \cdot \text{diag}(\sigma(g_m)).
Tensor indexing
zmsToIndexFact :: forall m. Fact m => Int -> Int Source #
Convert a \Z_m^* index to a linear tensor index in [m].
indexInfo :: forall m m'. m `Divides` m' => ([(Int, Int, Int)], Int, Int, [(Int, Int)]) Source #
A collection of useful information for working with tensor extensions. The first component is a list of triples (p,e,e') where e, e' are respectively the exponents of prime p in m, m'. The next two components are \varphi(m) and \varphi(m'). The final component is a pair ( \varphi(p^e), \varphi(p^{e'})) for each triple in the first component.
extIndicesPowDec :: forall m m'. m `Divides` m' => Vector Int Source #
A vector of \varphi(m) entries, where the ith entry is the index into the powerful/decoding basis of \O_{m'} of the ith entry of the powerful/decoding basis of \O_m.
extIndicesCRT :: forall m m'. m `Divides` m' => Vector Int Source #
A vector of \varphi(m) blocks of \varphi(m')/\varphi(m) consecutive entries. Each block contains all those indices into the CRT basis of \O_{m'} that "lie above" the corresponding index into the CRT basis of \O_m.
extIndicesCoeffs :: forall m m'. m `Divides` m' => Vector (Vector Int) Source #
The i_0th entry of the i_1th vector is
fromIndexPair
(i_1,i_0).
baseIndicesPow :: forall m m'. m `Divides` m' => Vector (Int, Int) Source #
A lookup table for toIndexPair
applied to indices [\varphi(m')].
baseIndicesDec :: forall m m'. m `Divides` m' => Vector (Maybe (Int, Bool)) Source #
A lookup table for baseIndexDec
applied to indices [\varphi(m')].
baseIndicesCRT :: forall m m'. m `Divides` m' => Vector Int Source #
Same as baseIndicesPow
, but only includes the second component
of each pair.