Skip to content

Commit

Permalink
use exported Vesta prime
Browse files Browse the repository at this point in the history
  • Loading branch information
martyall committed Jun 2, 2024
1 parent 7466e89 commit 91c10d7
Show file tree
Hide file tree
Showing 7 changed files with 14 additions and 12 deletions.
2 changes: 1 addition & 1 deletion cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -25,5 +25,5 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/l-adic/arithmetic-circuits.git
tag: 7d06e2b5df24237d8d694ca842ff1cd7e6609b34
tag: 7323152c3942c546d676ad6dcafe747f88d72663
--sha256: ngh2xhBSAu/2d4KlpCo5Aq8ezd6hX/MoNx26sLJzf0w=
3 changes: 2 additions & 1 deletion circuit/app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
module Main where

import Circuit (Vesta)
import Circom.CLI (defaultMain)
import Protolude
import ZK.Adder (Vesta, circuit)
import ZK.Adder (circuit)

main :: IO ()
main = defaultMain "adder" (circuit @Vesta)
11 changes: 6 additions & 5 deletions circuit/src/ZK/Adder.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,17 @@
{-# LANGUAGE PatternSynonyms #-}

module ZK.Adder (Vesta, circuit) where
module ZK.Adder (circuit) where

import Circuit
import Circuit.Language
import Data.Field.Galois (Prime, PrimeField)
import Data.Field.Galois (GaloisField)
import Data.Vector.Sized (index, pattern Build, pattern Nil, pattern (:<))
import Protolude

type Vesta = Prime 28948022309329048855892746252171976963363056481941647379679742748393362948097

circuit :: (Hashable f, PrimeField f) => ExprM f ()
circuit ::
Hashable f =>
GaloisField f =>
ExprM f ()
circuit = do
adder <- var_ <$> fieldInput Private "adder"
step_in <- map var_ <$> fieldInputs @2 Public "step_in"
Expand Down
2 changes: 1 addition & 1 deletion circuit/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Protolude
import R1CS (Witness (..))
import Test.Hspec
import Test.QuickCheck
import ZK.Adder (Vesta, circuit)
import ZK.Adder (circuit)

main :: IO ()
main = hspec $ do
Expand Down
4 changes: 2 additions & 2 deletions wasm-solver/adder-solver.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,8 @@ executable wasm-solver
"-optl-Wl,--export=init,--export=getNVars,--export=getVersion,--export=getRawPrime,--export=writeSharedRWMemory,--export=readSharedRWMemory,--export=getFieldNumLen32,--export=setInputSignal,--export=getInputSignalSize,--export=getWitnessSize,--export=getWitness,--export=getInputSize"

build-depends:
arithmetic-circuits:circom-compat
arithmetic-circuits
, arithmetic-circuits:circom-compat
, base >=4.10 && <5
, binary
, origami
, protolude
2 changes: 1 addition & 1 deletion wasm-solver/app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
module Main where

import Circuit (Vesta)
import Circom.Solver qualified as Circom
import Data.Binary (decodeFile)
import Data.IORef (IORef, newIORef)
import Protolude
import System.IO.Unsafe (unsafePerformIO)
import ZK.Adder (Vesta)

main :: IO ()
main = mempty
Expand Down
2 changes: 1 addition & 1 deletion wasm-solver/cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -24,5 +24,5 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/l-adic/arithmetic-circuits.git
tag: 7d06e2b5df24237d8d694ca842ff1cd7e6609b34
tag: 7323152c3942c546d676ad6dcafe747f88d72663
--sha256: ngh2xhBSAu/2d4KlpCo5Aq8ezd6hX/MoNx26sLJzf0w=

0 comments on commit 91c10d7

Please sign in to comment.