lol-0.7.0.0: A library for lattice cryptography.

Copyright(c) Eric Crockett 2011-2018
Chris Peikert 2011-2018
LicenseGPL-3
Maintainerecrockett0@gmail.com
Stabilityexperimental
PortabilityPOSIX \( \def\lcm{\text{lcm}} \)
Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.Cyclotomic.Linear

Description

Functions from one cyclotomic ring to another that are linear over a common subring.

Synopsis

Documentation

data Linear c (e :: Factored) (r :: Factored) (s :: Factored) z Source #

An \(E\)-linear function from \(R\) to \(S\).

Instances
Show (c s z) => Show (Linear c e r s z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

Methods

showsPrec :: Int -> Linear c e r s z -> ShowS #

show :: Linear c e r s z -> String #

showList :: [Linear c e r s z] -> ShowS #

NFData (c s z) => NFData (Linear c e r s z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

Methods

rnf :: Linear c e r s z -> () #

Additive (c s z) => C (Linear c e r s z) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

Methods

zero :: Linear c e r s z #

(+) :: Linear c e r s z -> Linear c e r s z -> Linear c e r s z #

(-) :: Linear c e r s z -> Linear c e r s z -> Linear c e r s z #

negate :: Linear c e r s z -> Linear c e r s z #

(Reflects e Word32, Reflects r Word32, Protoable (c s zq), ProtoType (c s zq) ~ RqProduct) => Protoable (Linear c e r s zq) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

Associated Types

type ProtoType (Linear c e r s zq) :: Type Source #

Methods

toProto :: Linear c e r s zq -> ProtoType (Linear c e r s zq) Source #

fromProto :: MonadError String m => ProtoType (Linear c e r s zq) -> m (Linear c e r s zq) Source #

Reduce (c s z) (c s zp) => Reduce (Linear c e r s z) (Linear c e r s zp) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

Methods

reduce :: Linear c e r s z -> Linear c e r s zp Source #

type LiftOf (Linear c e r s zp) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

type LiftOf (Linear c e r s zp) = Linear c e r s (LiftOf zp)
type ProtoType (Linear c e r s zq) Source # 
Instance details

Defined in Crypto.Lol.Cyclotomic.Linear

type ProtoType (Linear c e r s zq) = LinearRq

type ExtendLinCtx c e r s e' r' s' z = (e ~ FGCD r e', FLCM r e' `Divides` r', e' `Divides` s', s `Divides` s', ExtensionCyc c z, Additive (c s' z)) Source #

A convenient constraint synonym for extending a linear function to larger rings.

linearDec :: forall c e r s z. (e `Divides` r, e `Divides` s, Cyclotomic (c s z), ExtensionCyc c z) => [c s z] -> Linear c e r s z Source #

Construct an \(E\)-linear function given a list of its output values (in \(S\)) on the relative decoding basis of \(R/E\). The number of elements in the list must not exceed the size of the basis.

evalLin :: forall c e r s z. (e `Divides` r, e `Divides` s, Ring (c s z), ExtensionCyc c z) => Linear c e r s z -> c r z -> c s z Source #

Evaluates the given linear function on the input.

liftLin :: (LiftCyc (c s zp), LiftOf (c s zp) ~ c s (LiftOf zp)) => Maybe Basis -> Linear c e r s zp -> Linear c e r s (LiftOf zp) Source #

Lift the linear function in the specified basis (or any, if Nothing is given). The powerful basis is generally best, geometrically.

fmapLin :: (c s z -> c' s z) -> Linear c e r s z -> Linear c' e r s z Source #

Change the underlying cyclotomic representation.

extendLin :: forall c e r s e' r' s' z. ExtendLinCtx c e r s e' r' s' z => Linear c e r s z -> Linear c e' r' s' z Source #

Extend an \(E\)-linear function \(R\to S\) to an \(E'\)-linear function \(R'\to S'\).