arithmetic-circuits-0.2.0: Arithmetic circuits for zkSNARKs

Safe HaskellNone
LanguageHaskell2010

QAP

Contents

Description

Definitions of quadratic arithmetic programs, along with their assignment verification functions and the translations from single multiplication- or equality-gates into QAPs and arithmetic circuits into QAPs.

Synopsis

Documentation

data QapSet f Source #

The sets of polynomials/constants as they occur in QAPs, grouped into their constant, input, output and intermediate parts.

Constructors

QapSet 
Instances
Functor QapSet Source # 
Instance details

Defined in QAP

Methods

fmap :: (a -> b) -> QapSet a -> QapSet b #

(<$) :: a -> QapSet b -> QapSet a #

Foldable QapSet Source # 
Instance details

Defined in QAP

Methods

fold :: Monoid m => QapSet m -> m #

foldMap :: Monoid m => (a -> m) -> QapSet a -> m #

foldr :: (a -> b -> b) -> b -> QapSet a -> b #

foldr' :: (a -> b -> b) -> b -> QapSet a -> b #

foldl :: (b -> a -> b) -> b -> QapSet a -> b #

foldl' :: (b -> a -> b) -> b -> QapSet a -> b #

foldr1 :: (a -> a -> a) -> QapSet a -> a #

foldl1 :: (a -> a -> a) -> QapSet a -> a #

toList :: QapSet a -> [a] #

null :: QapSet a -> Bool #

length :: QapSet a -> Int #

elem :: Eq a => a -> QapSet a -> Bool #

maximum :: Ord a => QapSet a -> a #

minimum :: Ord a => QapSet a -> a #

sum :: Num a => QapSet a -> a #

product :: Num a => QapSet a -> a #

Eq f => Eq (QapSet f) Source # 
Instance details

Defined in QAP

Methods

(==) :: QapSet f -> QapSet f -> Bool #

(/=) :: QapSet f -> QapSet f -> Bool #

Show f => Show (QapSet f) Source # 
Instance details

Defined in QAP

Methods

showsPrec :: Int -> QapSet f -> ShowS #

show :: QapSet f -> String #

showList :: [QapSet f] -> ShowS #

Generic (QapSet f) Source # 
Instance details

Defined in QAP

Associated Types

type Rep (QapSet f) :: Type -> Type #

Methods

from :: QapSet f -> Rep (QapSet f) x #

to :: Rep (QapSet f) x -> QapSet f #

ToJSON f => ToJSON (QapSet f) Source # 
Instance details

Defined in QAP

FromJSON f => FromJSON (QapSet f) Source # 
Instance details

Defined in QAP

NFData f => NFData (QapSet f) Source # 
Instance details

Defined in QAP

Methods

rnf :: QapSet f -> () #

Pretty f => Pretty (QapSet f) Source # 
Instance details

Defined in QAP

Methods

pretty :: QapSet f -> Doc #

prettyList :: [QapSet f] -> Doc #

type Rep (QapSet f) Source # 
Instance details

Defined in QAP

type Rep (QapSet f) = D1 (MetaData "QapSet" "QAP" "arithmetic-circuits-0.2.0-6zOfGRHnhI9W2wAnMDkNU" False) (C1 (MetaCons "QapSet" PrefixI True) ((S1 (MetaSel (Just "qapSetConstant") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 f) :*: S1 (MetaSel (Just "qapSetInput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int f))) :*: (S1 (MetaSel (Just "qapSetIntermediate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int f)) :*: S1 (MetaSel (Just "qapSetOutput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int f)))))

data QAP f Source #

Quadratic arithmetic program

Constructors

QAP 
Instances
Eq f => Eq (QAP f) Source # 
Instance details

Defined in QAP

Methods

(==) :: QAP f -> QAP f -> Bool #

(/=) :: QAP f -> QAP f -> Bool #

Show f => Show (QAP f) Source # 
Instance details

Defined in QAP

Methods

showsPrec :: Int -> QAP f -> ShowS #

show :: QAP f -> String #

showList :: [QAP f] -> ShowS #

Generic (QAP f) Source # 
Instance details

Defined in QAP

Associated Types

type Rep (QAP f) :: Type -> Type #

Methods

from :: QAP f -> Rep (QAP f) x #

to :: Rep (QAP f) x -> QAP f #

(Generic f, ToJSON f) => ToJSON (QAP f) Source # 
Instance details

Defined in QAP

Methods

toJSON :: QAP f -> Value #

toEncoding :: QAP f -> Encoding #

toJSONList :: [QAP f] -> Value #

toEncodingList :: [QAP f] -> Encoding #

(FromJSON f, Generic f, Eq f, Num f) => FromJSON (QAP f) Source # 
Instance details

Defined in QAP

Methods

parseJSON :: Value -> Parser (QAP f) #

parseJSONList :: Value -> Parser [QAP f] #

NFData f => NFData (QAP f) Source # 
Instance details

Defined in QAP

Methods

rnf :: QAP f -> () #

(Eq f, Num f, Pretty f, Show f) => Pretty (QAP f) Source # 
Instance details

Defined in QAP

Methods

pretty :: QAP f -> Doc #

prettyList :: [QAP f] -> Doc #

type Rep (QAP f) Source # 
Instance details

Defined in QAP

type Rep (QAP f) = D1 (MetaData "QAP" "QAP" "arithmetic-circuits-0.2.0-6zOfGRHnhI9W2wAnMDkNU" False) (C1 (MetaCons "QAP" PrefixI True) ((S1 (MetaSel (Just "qapInputsLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QapSet (VPoly f))) :*: S1 (MetaSel (Just "qapInputsRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QapSet (VPoly f)))) :*: (S1 (MetaSel (Just "qapOutputs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (QapSet (VPoly f))) :*: S1 (MetaSel (Just "qapTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (VPoly f)))))

updateAtWire :: Wire -> a -> QapSet a -> QapSet a Source #

Update the value at the given wire label in the QapSet. (Partial function at the moment.)

lookupAtWire :: Wire -> QapSet a -> Maybe a Source #

Lookup the value at the given wire label in the QapSet.

sumQapSet :: Monoid g => QapSet g -> g Source #

Sum all the values contained in a QapSet.

sumQapSetCnstInp :: Monoid g => QapSet g -> g Source #

Sum only over constant and input values

sumQapSetMidOut :: Monoid g => QapSet g -> g Source #

Sum only over intermediate and output values

foldQapSet Source #

Arguments

:: (a -> a -> a)
  • commutative* binary operation
-> QapSet a

QapSet to fold over

-> a 

Fold over a QapSet with an operation that is assumed to be commutative.

combineWithDefaults Source #

Arguments

:: (a -> b -> c)

function to combine the values with

-> a

default left value

-> b

default right value

-> QapSet a

left QapSet

-> QapSet b

right QapSet

-> QapSet c 

combineInputsWithDefaults Source #

Arguments

:: (a -> b -> c)

function to combine the values with

-> a

default left value

-> b

default right value

-> QapSet a

left QapSet

-> QapSet b

right QapSet

-> QapSet c 

combineNonInputsWithDefaults Source #

Arguments

:: (a -> b -> c)

function to combine the values with

-> a

default left value

-> b

default right value

-> c

default constant

-> QapSet a

left QapSet

-> QapSet b

right QapSet

-> QapSet c 

verifyAssignment Source #

Arguments

:: (Eq f, Field f, Num f) 
=> QAP f

circuit whose evaluation we want to verify

-> QapSet f

vector containing the inputs, outputs and intermediate values (outputs of all the mul-gates)

-> Bool 

Verify whether an assignment of variables is consistent with the given QAP

verificationWitness Source #

Arguments

:: (Eq f, Field f, Num f) 
=> QAP f

circuit whose evaluation we want to verify

-> QapSet f

vector containing the inputs, outputs and intermediate values (outputs of all the mul-gates)

-> Maybe (VPoly f) 

Produce the polynomial witnessing the validity of given assignment against the given QAP. Will return Nothing if the assignment is not valid.

In Pinocchio's terminology: this produces the h(x) such that p(x) = h(x) * t(x) where t(x) is the target polynomial and p(x) is the left input polynomials times the right input polynomials minus the output polynomials.

verificationWitnessZk Source #

Arguments

:: (Eq f, Field f, Num f) 
=> f 
-> f 
-> f 
-> QAP f

circuit whose evaluation we want to verify

-> QapSet f

vector containing the inputs, outputs and intermediate values (outputs of all the mul-gates)

-> Maybe (VPoly f) 

gateToQAP Source #

Arguments

:: GaloisField k 
=> (Int -> k) 
-> [k]

arbitrarily chosen roots

-> Gate Wire k

circuit to encode as a QAP

-> QAP k 

Convert a single multiplication- or equality-gate into a QAP

gateToGenQAP Source #

Arguments

:: GaloisField k 
=> [k]

arbitrarily chosen roots

-> Gate Wire k

circuit to encode as a QAP

-> [GenQAP ((,) k) k] 

Convert a single multiplication gate (with affine circuits for inputs) into a GenQAP

initialQapSet Source #

Arguments

:: Num f 
=> Map Int f

inputs

-> QapSet f 

generateAssignmentGate Source #

Arguments

:: (Bits f, Fractional f) 
=> Gate Wire f

program

-> Map Int f

inputs

-> QapSet f 

Generate a valid assignment for a single gate.

generateAssignment Source #

Arguments

:: (Bits f, Fractional f) 
=> ArithCircuit f

program

-> Map Int f

inputs

-> QapSet f 

addMissingZeroes :: forall f. (Ord f, Num f) => [f] -> GenQAP (Map f) f -> GenQAP (Map f) f Source #

Add zeroes for those roots that are missing, to prevent the values in the GenQAP to be too sparse. (We can be sparse in wire values, but not in values at roots, otherwise the interpolation step is incorrect.)

arithCircuitToGenQAP Source #

Arguments

:: GaloisField k 
=> [[k]]

arbitrarily chosen roots, one for each gate

-> ArithCircuit k

circuit to encode as a QAP

-> GenQAP (Map k) k 

Convert an arithmetic circuit into a GenQAP: perform every step of the QAP translation except the final interpolation step.

arithCircuitToQAP Source #

Arguments

:: GaloisField k 
=> [[k]]

arbitrarily chosen roots, one for each gate

-> ArithCircuit k

circuit to encode as a QAP

-> QAP k 

Convert an arithmetic circuit into a QAP

arithCircuitToQAPFFT Source #

Arguments

:: GaloisField k 
=> (Int -> k)

function that gives us the primitive 2^k-th root of unity

-> [[k]]

arbitrarily chosen roots, one for each gate

-> ArithCircuit k

circuit to encode as a QAP

-> QAP k 

Convert an arithmetic circuit into a QAP

createPolynomials :: forall k. GaloisField k => GenQAP (Map k) k -> QAP k Source #

For the left inputright inputoutput polynomials: turn list of coordinates into a polynomial that interpolates the coordinates. For the target polynomial: define it as the product of all monics t_g(x) := x - r_g where r_g is the root corresponding to the gate g.

Naive construction of polynomials using Lagrange interpolation This has terrible complexity at the moment. Use the FFT-based approach if possible.

createPolynomialsFFT Source #

Arguments

:: GaloisField k 
=> (Int -> k)

function that gives us the primitive 2^k-th root of unity

-> GenQAP (Map k) k

GenQAP containing the coordinates we want to interpolate

-> QAP k 

Create polynomials using FFT-based polynomial operations instead of naive.

Orphan instances

ToJSON (Prime n) Source # 
Instance details

(ToJSON f, Generic f) => ToJSON (VPoly f) Source # 
Instance details

FromJSON (Prime n) Source # 
Instance details

(FromJSON f, Generic f, Eq f, Num f) => FromJSON (VPoly f) Source # 
Instance details

Pretty (Ratio Integer) Source # 
Instance details