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

Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Cyclotomic.Tensor

Contents

Description

Interface for cyclotomic tensors, and helper functions for tensor indexing.

Synopsis

Documentation

class (TElt t Double, TElt t (Complex Double)) => Tensor t where Source

Tensor encapsulates all the core 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.

The superclass constraint is for convenience, to ensure that we can sample error tensors of Doubles.

Associated Types

type TElt t r :: Constraint Source

Methods

entailIndexT :: Tagged (t m r) (Fact m :- (Applicative (t m), Traversable (t m))) Source

Properties that hold for any index. Use with \\.

entailFullT :: Tagged (t m r) ((Fact m, TElt t r) :- (Eq (t m r), ZeroTestable (t m r), Ring (t m r), NFData (t m r), Random (t m r))) Source

Properties that hold for any (legal) fully-applied tensor. Use with \\.

scalarPow :: (Fact m, TElt t r) => r -> t m r Source

Converts a scalar to a tensor in the powerful basis

l, lInv :: (Fact m, TElt t r) => t m r -> t m r Source

l converts from decoding-basis representation to powerful-basis representation; lInv is its inverse.

mulGPow, mulGDec :: (Fact m, TElt t r) => t m r -> t m r Source

Multiply by g in the powerful/decoding basis

divGPow, divGDec :: (Fact m, TElt t r) => t m r -> Maybe (t m r) Source

Divide by g in the powerful/decoding basis. The Maybe output indicates that the operation may fail, which happens exactly when the input is not divisible by g.

crtFuncs :: (Fact m, TElt t r, CRTrans r) => Maybe (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.

tGaussianDec :: (Fact m, OrdFloat q, Random q, TElt t q, ToRational v, MonadRandom rnd) => v -> rnd (t m q) Source

Sample from the "skewed" Gaussian error distribution t*D in the decoding basis, where D has scaled variance v.

twacePowDec :: (m `Divides` m', TElt t r) => t m' r -> t m r Source

The twace linear transformation, which is the same in both the powerful and decoding bases.

embedPow, embedDec :: (m `Divides` m', TElt t r) => t m r -> t m' r Source

The embed linear transformations, for the powerful and decoding bases.

crtExtFuncs :: (m `Divides` m', TElt t r, CRTrans r) => Maybe (t m' r -> t m r, t m r -> t m' r) Source

A tuple of all the extension-related operations involving the CRT bases, 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 twaceCRT, embedCRT.

coeffs :: (m `Divides` m', TElt t r) => t m' r -> [t m r] Source

Map a tensor in the powerful/decoding/CRT basis, representing an O_m' element, to a vector of tensors representing O_m elements in the same kind of basis.

powBasisPow :: (m `Divides` m', TElt t r) => Tagged m [t m' r] Source

The powerful extension basis w.r.t. the powerful basis.

crtSetDec :: (m `Divides` m', PrimeField fp, Coprime (PToF (CharOf fp)) m', TElt t fp) => Tagged m [t m' fp] Source

A list of tensors representing the mod-p CRT set of the extension.

fmapT :: (Fact m, TElt t a, TElt t b) => (a -> b) -> t m a -> t m b Source

Potentially optimized version of fmap when the input and output element types satisfy TElt.

fmapTM :: (Monad mon, Fact m, TElt t a, TElt t b) => (a -> mon b) -> t m a -> mon (t m b) Source

Potentially optimized monadic fmap.

Top-level CRT functions

hasCRTFuncs :: forall t m r. (Tensor t, Fact m, TElt t r, CRTrans r) => TaggedT (t m r) Maybe () Source

Convenience value indicating whether crtFuncs exists.

scalarCRT :: (Tensor t, Fact m, TElt t r, CRTrans r) => Maybe (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 :: (Tensor t, Fact m, TElt t r, CRTrans r) => Maybe (t m r -> t m r) Source

Multiply by g in the CRT basis. (This function is simply an appropriate entry from crtFuncs.)

divGCRT :: (Tensor t, Fact m, TElt t r, CRTrans r) => Maybe (t m r -> t m r) Source

Divide by g in the CRT basis. (This function is simply an appropriate entry from crtFuncs.)

crt :: (Tensor t, Fact m, TElt t r, CRTrans r) => Maybe (t m r -> t m r) Source

The CRT transform. (This function is simply an appropriate entry from crtFuncs.)

crtInv :: (Tensor t, Fact m, TElt t r, CRTrans r) => Maybe (t m r -> t m r) Source

The inverse CRT transform. (This function is simply an appropriate entry from crtFuncs.)

twaceCRT :: forall t r m m'. (Tensor t, m `Divides` m', TElt t r, CRTrans r) => Maybe (t m' r -> t m r) Source

The "tweaked trace" function for tensors in the CRT basis: For cyclotomic indices m | m', Tw(x) = (mhat/m'hat) * Tr(g'/g * x). (This function is simply an appropriate entry from crtExtFuncs.)

embedCRT :: forall t r m m'. (Tensor t, m `Divides` m', TElt t r, CRTrans r) => Maybe (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.)

Tensor indexing

data Matrix r Source

A Kronecker product of zero of more matrices over r.

indexM :: Ring r => Matrix r -> Int -> Int -> r Source

Extract the (i,j) element of a Matrix.

twCRTs :: (Fact m, CRTrans r) => TaggedT m Maybe (Matrix r) Source

The "tweaked" CRT^* matrix: CRT^* . diag(sigma(g_m)).

zmsToIndexFact :: Fact m => Tagged m (Int -> Int) Source

Convert a Z_m^* index to a linear tensor index in [m].

indexInfo :: forall m m'. m `Divides` m' => Tagged `(m, 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 phi(m) and phi(m'). The final component is a pair (phi(p^e), phi(p^e')) for each triple in the first component.

extIndicesPowDec :: m `Divides` m' => Tagged `(m, m')` (Vector Int) Source

A vector of phi(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' => Tagged `(m, m')` (Vector Int) Source

A vector of phi(m) blocks of phi(m')/phi(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' => Tagged `(m, m')` (Vector (Vector Int)) Source

The i0th entry of the i1th vector is fromIndexPair (i1,i0).

baseIndicesPow :: forall m m'. m `Divides` m' => Tagged `(m, m')` (Vector (Int, Int)) Source

A lookup table for toIndexPair applied to indices [phi(m')].

baseIndicesDec :: forall m m'. m `Divides` m' => Tagged `(m, m')` (Vector (Maybe (Int, Bool))) Source

A lookup table for baseIndexDec applied to indices [phi(m')].

baseIndicesCRT :: forall m m'. m `Divides` m' => Tagged `(m, m')` (Vector Int) Source

Same as baseIndicesPow, but only includes the second component of each pair.

digitRev :: PP -> Int -> Int Source

Base-p digit reversal; input and output are in [p^e].