lol-0.7.0.0: A library for lattice cryptography.

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

Crypto.Lol.Cyclotomic.Tensor

Contents

Description

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

Synopsis

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 \(\O_{m'}\) element, to a vector of tensors representing \(\O_m\) elements in the same kind of basis.

powBasisPow :: m `Divides` m' => Tagged m [t m' r] Source #

The relative powerful basis of \( \O_{m'}/\O_{m} \), w.r.t. the powerful basis of \( \O_{m'} \).

class TensorPowDec t r => TensorG t r where Source #

Encapsulates multiplication and division by \(g_m\)

Methods

mulGPow :: Fact m => t m r -> t m r Source #

Multiply by \(g_m\) in the powerful/decoding basis

mulGDec :: Fact m => t m r -> t m r Source #

Multiply by \(g_m\) in the powerful/decoding basis

divGPow :: Fact m => t m r -> Maybe (t m r) Source #

Divide by \(g_m\) 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_m\).

divGDec :: Fact m => t m r -> Maybe (t m r) Source #

Divide by \(g_m\) 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_m\).

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 #

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.

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\cdot 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 \(g_m \cdot e\) under the canonical embedding, namely, \(\hat{m}^{-1} \cdot \| \sigma(g_m \cdot e) \|^2\).

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.

Methods

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

Relative mod-p CRT set of \( \O_{m'}/\O_{m} \) in the decoding basis.

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

data Kron r Source #

A Kronecker product of zero of more matrices over r.

indexK :: Ring r => Kron r -> Int -> Int -> r Source #

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

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 \(m\)th 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 \(m\)th 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 \(i\)th entry is the index into the powerful/decoding basis of \(\O_{m'}\) of the \(i\)th 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_0\)th entry of the \(i_1\)th 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.

digitRev :: PP -> Int -> Int Source #

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