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

Safe HaskellNone
LanguageHaskell2010

Crypto.Lol.LatticePrelude

Contents

Description

A substitute for the Prelude that is more suitable for Lol. This module exports most of the Numeric Prelude and other frequently used modules, plus some low-level classes, missing instances, and assorted utility functions.

Synopsis

Classes

class Enumerable a where Source

Poor man's Enum.

Methods

values :: [a] Source

Instances

GFCtx k fp deg => Enumerable (GF k fp deg) Source 
(ReflectsTI k q z, Enum z) => Enumerable (ZqBasic k q z) Source 

class (ToInteger (ModRep a), Additive a) => Mod a where Source

Represents a quotient group modulo some integer.

Associated Types

type ModRep a Source

Methods

modulus :: Tagged a (ModRep a) Source

Instances

(Mod a, Mod b) => Mod (a, b) Source 
ReflectsTI k q z => Mod (ZqBasic k q z) Source 

class (Additive a, Additive b) => Reduce a b where Source

Represents that b is a quotient group of a.

Methods

reduce :: a -> b Source

Instances

(Reduce a b1, Reduce a b2) => Reduce a (b1, b2) Source 
(Reflects k q z, Ring (ZqBasic k q z)) => Reduce Integer (ZqBasic k q z) Source 
ReflectsTI k q z => Reduce z (ZqBasic k q z) Source 
(Reduce a b, Fact m, CElt t a, CElt t b) => Reduce (UCyc t m a) (UCyc t m b) Source 
(Reduce a b, Fact m, CElt t a, CElt t b) => Reduce (Cyc t m a) (Cyc t m b) Source 
(Reduce z zq, Fact s, CElt t z, CElt t zq) => Reduce (Linear t z e r s) (Linear t zq e r s) Source 

type Lift b a = (Lift' b, LiftOf b ~ a) Source

Represents that b can be lifted to a "short" a congruent to b.

class Reduce (LiftOf b) b => Lift' b where Source

Fun-dep version of Lift.

Associated Types

type LiftOf b Source

Methods

lift :: b -> LiftOf b Source

Instances

(Mod a, Mod b, Lift' a, Lift' b, Reduce Integer (a, b), ToInteger (LiftOf a), ToInteger (LiftOf b)) => Lift' (a, b) Source 
ReflectsTI k q z => Lift' (ZqBasic k q z) Source 
(CElt t zp, CElt t z, (~) * z (LiftOf zp), Lift zp z, Fact s) => Lift' (Linear t zp e r s) Source 

class (Additive a, Additive b) => Rescale a b where Source

Represents that a can be rescaled to b, as an "approximate" additive homomorphism.

Methods

rescale :: a -> b Source

Instances

(Ring b, Mod a, Reduce (ModRep a) b) => Rescale b (a, b) Source 
(Ring a, Mod b, Reduce (ModRep b) a) => Rescale a (a, b) Source 
(Rescale ((a, b), c) (a, b), Rescale (a, b) a) => Rescale ((a, b), c) a Source 
(Rescale (a, (b, c)) (b, c), Rescale (b, c) c) => Rescale (a, (b, c)) c Source 
(Mod b, Field a, Lift b (ModRep b), Reduce (LiftOf b) a) => Rescale (a, b) a Source 
(Mod a, Field b, Lift a (ModRep a), Reduce (LiftOf a) b) => Rescale (a, b) b Source 
(ReflectsTI k q z, ReflectsTI k1 q' z, Ring z) => Rescale (ZqBasic k q z) (ZqBasic k q' z) Source 

class (Field src, Field tgt) => Encode src tgt where Source

Represents that the target ring can "noisily encode" values from the source ring, in either "most significant digit" (MSD) or "least significant digit" (LSD) encodings, and provides conversion factors between the two types of encodings.

Methods

lsdToMSD :: (src, tgt) Source

The factor that converts an element from LSD to MSD encoding in the target field, with associated scale factor to apply to correct the resulting encoded value.

Instances

(Encode s t1, Encode s t2, Field (t1, t2)) => Encode s (t1, t2) Source 
(Reflects k p z, ReflectsTI k1 q z, Field (ZqBasic k p z), Field (ZqBasic k1 q z)) => Encode (ZqBasic k p z) (ZqBasic k q z) Source 

msdToLSD :: Encode src tgt => (src, tgt) Source

Inverted entries of lsdToMSD.

Numeric

max :: Ord a => a -> a -> a Source

The Prelude definition of max.

min :: Ord a => a -> a -> a Source

The Prelude definition of min.

abs :: Absolute a => a -> a Source

The sane definition of abs from Numeric rather than the default from NumericPrelude.

realToField :: (Field b, ToRational a) => a -> b Source

The hidden NP function from ToRational.

type ZeroTestable a = C a Source

Sane synonym for C.

type Additive a = C a Source

Sane synonym for C.

type Ring a = C a Source

Sane synonym for C.

type Module a v = C a v Source

Sane synonym for C.

type IntegralDomain a = C a Source

Sane synonym for C.

type ToRational a = C a Source

Sane synonym for C.

type Field a = C a Source

Sane synonym for C.

type RealRing a = C a Source

Sane synonym for C.

type RealField a = C a Source

Sane synonym for C.

type Algebraic a = C a Source

Sane synonym for C.

type Transcendental a = C a Source

Sane synonym for C.

type RealTranscendental a = C a Source

Sane synonym for C.

type OrdFloat a = (Ord a, Transcendental a) Source

Convenient synonym for (Ord a, Transcendental a)

type ToInteger a = C a Source

Sane synonym for C.

type Absolute a = C a Source

Sane synonym for C.

type RealIntegral a = C a Source

Sane synonym for C.

type PID a = C a Source

Sane synonym for C.

type Polynomial a = T a Source

Sane synonym for T.

(^) :: forall a i. (Ring a, ToInteger i) => a -> i -> a Source

Our custom exponentiation, overriding NP's version that requires Integer exponent. Copied from http://hackage.haskell.org/package/base-4.7.0.0/docs/src/GHC-Real.html#%5E

modinv :: (PID i, Eq i) => i -> i -> Maybe i Source

Inverse of a modulo q, in range 0..q-1. (Argument order is infix-friendly.)

decomp :: (IntegralDomain z, Ord z) => [z] -> z -> [z] Source

Decompose an element into a list of "centered" digits with respect to relative radices.

logCeil :: ToInteger i => i -> i -> Int Source

Yield ceil (log_b(x)).

roundMult :: (RealField r, ToInteger i) => i -> r -> i Source

Deterministically round to the nearest multiple of i.

roundScalarCentered :: (RealField r, Random r, ToInteger i, MonadRandom mon) => i -> r -> mon i Source

Randomly round to the nearest larger or smaller multiple of i, where the round-off term has expectation zero.

divModCent :: (IntegralDomain i, Ord i) => i -> i -> (i, i) Source

Variant of divMod in which the remainder is in the range [-b/2,b/2).

Complex

data Complex a Source

Newtype wrapper (with slightly different instances) for numeric-prelude Complex.

roundComplex :: (RealRing a, ToInteger b) => Complex a -> (b, b) Source

Rounds the real and imaginary components to the nearest integer.

cis :: Transcendental a => a -> Complex a Source

cis t is a complex value with magnitude 1 and phase t (modulo 2*Pi).

real :: Complex a -> a Source

Real component of a complex number.

imag :: Complex a -> a Source

Imaginary component of a complex number.

fromReal :: Additive a => a -> Complex a Source

Embeds a scalar as the real component of a complex number.

Factored

Miscellaneous

rescaleMod :: forall a b. (Mod a, Mod b, ModRep a ~ ModRep b, Lift a (ModRep b), Ring b) => a -> b Source

A default implementation of rescaling for Mod types.

roundCoset :: forall zp z r. (Mod zp, z ~ ModRep zp, Lift zp z, RealField r) => zp -> r -> z Source

Deterministically round to a nearby value in the desired coset

pureT :: Applicative f => TaggedT t Identity a -> TaggedT t f a Source

Apply any applicative to a Tagged value.

peelT :: Tagged t (f a) -> TaggedT t f a Source

Expose the monad of a tagged value.

pasteT :: TaggedT t f a -> Tagged t (f a) Source

Hide the monad of a tagged value.

withWitness :: forall n r. (SingI n => Tagged n r) -> Sing n -> r Source

Use a singleton as a witness to extract a value from a tagged value.

withWitnessT :: forall n mon r. Monad mon => (SingI n => TaggedT n mon r) -> Sing n -> mon r Source

Monadic version of withWitness.

module Data.Proxy