Coder Social home page Coder Social logo

sdiehl / arithmetic-circuits Goto Github PK

View Code? Open in Web Editor NEW
82.0 7.0 13.0 336 KB

Arithmetic circuits for zero knowledge proof systems

Home Page: https://www.adjoint.io

License: MIT License

Haskell 98.36% Nix 1.64%
arithmetic-circuit zksnarks compiler zk-snarks qap zero-knowledge

arithmetic-circuits's Introduction

Adjoint Logo

CircleCI

Arithmetic Circuits

An arithmetic circuit is a low-level representation of a program that consists of gates computing arithmetic operations of addition and multiplication, with wires connecting the gates.

This form allows us to express arbitrarily complex programs with a set of private inputs and public inputs whose execution can be publicly verified without revealing the private inputs. This construction relies on recent advances in zero-knowledge proving systems:

This library presents a low-level interface for building zkSNARK proving systems from higher-level compilers. This system depends on the following cryptographic dependenices.

Theory

Towers of Finite Fields

This library can build proof systems polymorphically over a variety of pairing friendly curves. By default we use the BN254 with an efficient implementation of the optimal Ate pairing.

The Barreto-Naehrig (BN) family of curves achieve high security and efficiency with pairings due to an optimum embedding degree and high 2-adicity. We have implemented the optimal Ate pairing over the BN254 curve we define and as:

The tower of finite fields we work with is defined as:

Arithmetic circuits

Arithmetic Circuit

An arithmetic circuit over a finite field is a directed acyclic graph with gates as vertices and wires and edges. It consists of a list of multiplication gates together with a set of linear consistency equations relating the inputs and outputs of the gates.

Let be a finite field and a map that takes arguments as inputs from and outputs l elements in . The function C is an arithmetic circuit if the value of the inputs that pass through wires to gates are only manipulated according to arithmetic operations + or x (allowing constant gates).

Let , , respectively denote the input, witness and output size and be the number of all inputs and outputs of the circuit A tuple , is said to be a valid assignment for an arithmetic circuit C if .

Quadratic Arithmetic Programs (QAP)

QAPs are encodings of arithmetic circuits that allow the prover to construct a proof of knowledge of a valid assignment for a given circuit .

A quadratic arithmetic program (QAP) contains three sets of polynomials in :

, ,

and a target polynomial .

In this setting, an assignment is valid for a circuit if and only if the target polynomial divides the polynomial:

Logical circuits can be written in terms of the addition, multiplication and negation operations.

DSL and Circuit Builder Monad

Any arithmetic circuit can be built using a domain specific language to construct circuits that lives inside Lang.hs.

type ExprM f a = State (ArithCircuit f, Int) a
execCircuitBuilder :: ExprM f a -> ArithCircuit f
-- | Binary arithmetic operations
add, sub, mul :: Expr Wire f f -> Expr Wire f f -> Expr Wire f f
-- | Binary logic operations
-- Have to use underscore or similar to avoid shadowing @and@ and @or@
-- from Prelude/Protolude.
and_, or_, xor_ :: Expr Wire f Bool -> Expr Wire f Bool -> Expr Wire f Bool
-- | Negate expression
not_ :: Expr Wire f Bool -> Expr Wire f Bool
-- | Compare two expressions
eq :: Expr Wire f f -> Expr Wire f f -> Expr Wire f Bool
-- | Convert wire to expression
deref :: Wire -> Expr Wire f f
-- | Return compilation of expression into an intermediate wire
e :: Num f => Expr Wire f f -> ExprM f Wire
-- | Conditional statement on expressions
cond :: Expr Wire f Bool -> Expr Wire f ty -> Expr Wire f ty -> Expr Wire f ty
-- | Return compilation of expression into an output wire
ret :: Num f => Expr Wire f f -> ExprM f Wire

The following program represents the image of the arithmetic circuit above.

program :: ArithCircuit Fr
program = execCircuitBuilder (do
  i0 <- fmap deref input
  i1 <- fmap deref input
  i2 <- fmap deref input
  let r0 = mul i0 i1
      r1 = mul r0 (add i0 i2)
  ret r1)

The output of an arithmetic circuit can be converted to a DOT graph and save it as SVG.

dotOutput :: Text
dotOutput = arithCircuitToDot (execCircuitBuilder program)

Example

We'll keep taking the program constructed with our DSL as example and will use the library pairing that provides a field of points of the BN254 curve and precomputes primitive roots of unity for binary powers that divide .

import Protolude

import qualified Data.Map as Map
import Data.Pairing.BN254 (Fr, getRootOfUnity)

import Circuit.Arithmetic
import Circuit.Expr
import Circuit.Lang
import Fresh (evalFresh, fresh)
import QAP

program :: ArithCircuit Fr
program = execCircuitBuilder (do
  i0 <- fmap deref input
  i1 <- fmap deref input
  i2 <- fmap deref input
  let r0 = mul i0 i1
      r1 = mul r0 (add i0 i2)
  ret r1)

We need to generate the roots of the circuit to construct polynomials and that satisfy the divisibility property and encode the circuit to a QAP to allow the prover to construct a proof of a valid assignment.

We also need to give values to the three input wires to this arithmetic circuit.

roots :: [[Fr]]
roots = evalFresh (generateRoots (fmap (fromIntegral . (+ 1)) fresh) program)

qap :: QAP Fr
qap = arithCircuitToQAPFFT getRootOfUnity roots program

inputs :: Map.Map Int Fr
inputs = Map.fromList [(0, 7), (1, 5), (2, 4)]

A prover can now generate a valid assignment.

assignment :: QapSet Fr
assignment = generateAssignment program inputs

The verifier can check the divisibility property of by for the given circuit.

main :: IO ()
main = do
  if verifyAssignment qap assignment
    then putText "Valid assignment"
    else putText "Invalid assignment"

See Example.hs.

Disclaimer

This is experimental code meant for research-grade projects only. Please do not use this code in production until it has matured significantly.

License

Copyright (c) 2017-2020 Adjoint Inc.

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM,
DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR
OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE
OR OTHER DEALINGS IN THE SOFTWARE.

arithmetic-circuits's People

Contributors

acentelles avatar bodigrim avatar sdiehl avatar texify[bot] avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar

arithmetic-circuits's Issues

Problem with `stack test`

on current master (18e15de)
I get the following error on stack test

pairing            > [10 of 11] Compiling Data.Pairing.Hash
pairing            >
pairing            > /tmp/stack-9ebfe010c6b08242/pairing-1.0.0/src/Data/Pairing/Hash.hs:48:12: error:
pairing            >     • Could not deduce (Bits (Prime q))
pairing            >         arising from a use of ‘fromBytes’
pairing            >       from the context: (MonadRandom m, ECPairing e q r u v w)
pairing            >         bound by the type signature for:
pairing            >                    swEncBN :: forall e (m :: * -> *) (q :: Nat) (r :: Nat) u v w.
pairing            >                               (MonadRandom m, ECPairing e q r u v w) =>
pairing            >                               ByteString -> m (Maybe (G1 e))
pairing            >         at src/Data/Pairing/Hash.hs:(44,1)-(45,35)
pairing            >     • In the expression: fromBytes bs
pairing            >       In an equation for ‘t’: t = fromBytes bs
pairing            >       In the second argument of ‘($)’, namely
pairing            >         ‘do sqrt3 <- hoistMaybe $ sr $ - 3
pairing            >             let t = fromBytes bs
pairing            >                 s1 = (sqrt3 - 1) / 2
pairing            >                 ....
pairing            >             guard (b1 + t * t /= 0)
pairing            >             if t == 0 then
pairing            >                 if b1 == 3 then
pairing            >                     return $ A (- 1) 1
pairing            >                 else
pairing            >                     if b1 == 4 then return $ A 1 2 else ...
pairing            >             else
pairing            >                 do let ...
pairing            >                    ....’
pairing            >    |
pairing            > 48 |   let t  = fromBytes bs
pairing            >    |            ^^^^^^^^^^^^
pairing            >

Is building / testing with stack supported?
I realize that this is for pairing. I can build / test pairing master without problem, but its 1.0 tag cannot be build. arithemtic-circuits requires >= 1.0 and < 1.1

~/s/g/H/K/pairing ((1.0)|✔) $ stack build                              
                                                                                                                                                                                
Error: While constructing the build plan, the following exceptions were encountered:                         
                                                               
In the dependencies for poly-0.3.2.0:                                  
    vector-algorithms-0.8.0.1 from stack configuration does not match >=0.8.0.3  (latest matching version is 0.8.0.3)                                                           
needed due to pairing-1.0.0 -> poly-0.3.2.0                            

Maybe that is the problem?

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.