Skip to content

Commit 4762e95

Browse files
committed
add json opts for witness
1 parent a2e0794 commit 4762e95

File tree

3 files changed

+31
-9
lines changed

3 files changed

+31
-9
lines changed

Diff for: circom-compat/src/Circom/CLI.hs

+16-8
Original file line numberDiff line numberDiff line change
@@ -55,9 +55,9 @@ data Command
5555
| Solve SolveOpts
5656

5757
data CompileOpts = CompileOpts
58-
{ optimizeOpts :: OptimizeOpts,
59-
genDotFile :: Bool,
60-
includeJson :: Bool
58+
{ coOptimizeOpts :: OptimizeOpts,
59+
coGenDotFile :: Bool,
60+
coIncludeJson :: Bool
6161
}
6262

6363
compileOptsParser :: Parser CompileOpts
@@ -86,7 +86,8 @@ optimizeOptsParser =
8686
)
8787

8888
data SolveOpts = SolveOpts
89-
{ inputsFile :: FilePath
89+
{ soInputsFile :: FilePath,
90+
soIncludeJson :: Bool
9091
}
9192

9293
solveOptsParser :: Parser SolveOpts
@@ -98,6 +99,10 @@ solveOptsParser =
9899
<> showDefault
99100
<> value "inputs.json"
100101
)
102+
<*> switch
103+
( long "json"
104+
<> help "also write json versions of artifacts"
105+
)
101106

102107
defaultMain ::
103108
forall f a.
@@ -111,25 +116,28 @@ defaultMain progName program = do
111116
case cmd opts of
112117
Compile compilerOpts -> do
113118
let BuilderState {..} = snd $ runCircuitBuilder program
114-
prog = optimize (optimizeOpts compilerOpts) $ mkCircomProgram bsVars bsCircuit
119+
prog = optimize (coOptimizeOpts compilerOpts) $ mkCircomProgram bsVars bsCircuit
115120
r1cs = r1csToCircomR1CS $ toR1CS (cpVars prog) (cpCircuit prog)
116121
createDirectoryIfMissing True outDir
117122
encodeFile (r1csFilePath outDir) r1cs
118123
encodeFile (binFilePath outDir) prog
119124
-- We generarate a template json file for the inputs with default values set to null
120125
let inputsTemplate = map (const A.Null) $ labelToVar $ cvInputsLabels $ cpVars prog
121126
A.encodeFile (inputsTemplateFilePath outDir) inputsTemplate
122-
when (includeJson compilerOpts) $ do
127+
when (coIncludeJson compilerOpts) $ do
123128
A.encodeFile (r1csFilePath outDir <> ".json") (map fromP r1cs)
124-
when (genDotFile compilerOpts) $ do
129+
A.encodeFile (binFilePath outDir <> ".json") (map fromP prog)
130+
when (coGenDotFile compilerOpts) $ do
125131
writeFile (dotFilePath outDir) $ arithCircuitToDot (cpCircuit prog)
126132
Solve solveOpts -> do
127133
inputs <- do
128-
mInputs <- decodeFileStrict (inputsFile solveOpts)
134+
mInputs <- decodeFileStrict (soInputsFile solveOpts)
129135
maybe (panic "Failed to decode inputs") (pure . map (fromInteger @f)) mInputs
130136
circuit <- decodeFile (binFilePath outDir)
131137
let wtns = nativeGenWitness circuit inputs
132138
encodeFile (witnessFilePath outDir) wtns
139+
when (soIncludeJson solveOpts) $ do
140+
A.encodeFile (witnessFilePath outDir <> ".json") (map fromP wtns)
133141
where
134142
baseFilePath :: FilePath -> FilePath
135143
baseFilePath dir = dir <> "/" <> Text.unpack progName

Diff for: circom-compat/src/Circom/Solver.hs

+10
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ where
2525

2626
import Circom.R1CS (CircomWitness, FieldSize (..), circomReindexMap, integerFromLittleEndian, integerToLittleEndian, n32, witnessToCircomWitness)
2727
import Circuit
28+
import Data.Aeson (ToJSON)
2829
import Data.Binary (Binary)
2930
import Data.Field.Galois (GaloisField, PrimeField (fromP), char)
3031
import Data.IORef (IORef, readIORef, writeIORef)
@@ -47,6 +48,15 @@ data CircomProgram f = CircomProgram
4748

4849
instance (Binary f) => Binary (CircomProgram f)
4950

51+
instance Functor CircomProgram where
52+
fmap f CircomProgram {cpVars, cpCircuit} =
53+
CircomProgram
54+
{ cpVars,
55+
cpCircuit = fmap f cpCircuit
56+
}
57+
58+
instance (ToJSON f) => ToJSON (CircomProgram f)
59+
5060
mkCircomProgram ::
5161
CircuitVars Text ->
5262
ArithCircuit f ->

Diff for: circuit/src/Circuit/Arithmetic.hs

+5-1
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ import Circuit.Affine
3030
( AffineCircuit (..),
3131
evalAffineCircuit,
3232
)
33-
import Data.Aeson (FromJSON, ToJSON)
33+
import Data.Aeson (FromJSON, ToJSON, ToJSONKey)
3434
import Data.Binary (Binary)
3535
import Data.Field.Galois (PrimeField, fromP)
3636
import Data.IntMap qualified as IntMap
@@ -300,6 +300,8 @@ data CircuitVars label = CircuitVars
300300

301301
instance (Binary label) => Binary (CircuitVars label)
302302

303+
instance (ToJSON label, ToJSONKey label) => ToJSON (CircuitVars label)
304+
303305
instance (Pretty label) => Pretty (CircuitVars label) where
304306
pretty CircuitVars {cvVars, cvPrivateInputs, cvPublicInputs, cvOutputs, cvInputsLabels} =
305307
vcat
@@ -407,6 +409,8 @@ data InputBindings label = InputBindings
407409

408410
instance (Binary label) => Binary (InputBindings label)
409411

412+
instance (ToJSON label, ToJSONKey label) => ToJSON (InputBindings label)
413+
410414
mapLabels :: (Ord l2) => (l1 -> l2) -> InputBindings l1 -> InputBindings l2
411415
mapLabels f InputBindings {labelToVar, varToLabel} =
412416
InputBindings

0 commit comments

Comments
 (0)