Skip to content

Commit 6ff525e

Browse files
Acentellessdiehl
authored andcommitted
Use BLS12381 curve (#5)
* Use BLS12381 curve * Address imports PR feedback * Add benchmarks * Update Galois fields, elliptic curves, and pairings
1 parent ada5e75 commit 6ff525e

21 files changed

+227
-153
lines changed

ChangeLog.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,11 @@
11
# Changelog for sonic
22

3+
## 0.3
4+
5+
* Use BLS12-381 elliptic curve
6+
* Add `RndOracle` data type as part of the proving step
7+
* Add benchmarks
8+
39
## 0.2
410

511
* Fix leak: Prover should not receive `x` and `g^{\alpha}` should not be shared.

README.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ the two-variate polynomial equation used in
2020

2121
The Sonic protocol can be outlined in three steps: Setup, Prover and
2222
Verifier. Due to the universality property of the SRS, the setup phase needs
23-
only to be run once.
23+
only to be run once. This implementation uses BLS12-381 elliptic curve.
2424

2525
```haskell
2626
sonicProtocol :: ArithCircuit Fr -> Assignment Fr -> Fr -> IO Bool

bench/Main.hs

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
module Main where
2+
3+
import Protolude
4+
import Bulletproofs.ArithmeticCircuit (Assignment(..), ArithCircuit)
5+
import Criterion.Main
6+
import Data.Pairing.BLS12381 (Fr)
7+
8+
import qualified Sonic.SRS as SRS
9+
import Sonic.Protocol
10+
import Test.Reference
11+
12+
exampleX :: Fr
13+
exampleX = 11
14+
15+
exampleZ :: Fr
16+
exampleZ = 12
17+
18+
exampleD :: Int -> Int
19+
exampleD n = 25 * n
20+
21+
exampleRndParams :: RandomParams
22+
exampleRndParams = RandomParams
23+
{ pX = 1
24+
, pY = 2
25+
, pZ = 3
26+
, pAlpha = 4
27+
}
28+
29+
runProver :: IO (Proof Fr, RndOracle Fr)
30+
runProver = do
31+
let (arithCircuit, assignment) = arithCircuitExample1 exampleX exampleZ
32+
srs = SRS.new (exampleD (length $ aL assignment)) (pX exampleRndParams) (pAlpha exampleRndParams)
33+
prove srs assignment arithCircuit
34+
35+
main :: IO ()
36+
main = defaultMain
37+
[ sonic $ arithCircuitExample1 exampleX exampleZ
38+
, sonic $ arithCircuitExample2 exampleX exampleZ
39+
]
40+
41+
sonic :: (ArithCircuit Fr, Assignment Fr) -> Benchmark
42+
sonic (arithCircuit, assignment) = bgroup "Sonic"
43+
[ bench "Prover" $
44+
let srs = SRS.new (exampleD (length $ aL assignment)) (pX exampleRndParams) (pAlpha exampleRndParams)
45+
in nfIO (prove srs assignment arithCircuit)
46+
, env runProver $ \(~(proof, rndOracle@RndOracle{..})) ->
47+
bench "Verifier" $
48+
let srs = SRS.new (exampleD (length $ aL assignment)) (pX exampleRndParams) (pAlpha exampleRndParams)
49+
in nf (verify srs arithCircuit proof rndOracleY rndOracleZ) rndOracleYs
50+
]

examples/Main.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -4,20 +4,20 @@ module Main where
44
import Protolude
55
import Control.Monad.Random (getRandomR)
66
import Bulletproofs.ArithmeticCircuit
7-
import GaloisField(GaloisField(rnd))
7+
import Data.Pairing.BLS12381 (Fr)
8+
import Data.Field.Galois (rnd)
89

910
import Sonic.SRS as SRS
1011
import Sonic.Protocol
11-
import Sonic.Curve (Fr)
1212

1313
sonicProtocol :: ArithCircuit Fr -> Assignment Fr -> Fr -> IO Bool
1414
sonicProtocol circuit assignment x = do
1515
-- Setup for an SRS
1616
srs <- SRS.new <$> randomD n <*> pure x <*> rnd
1717
-- Prover
18-
(proof, y, z, ys) <- prove srs assignment circuit
18+
(proof, rndOracle@RndOracle{..}) <- prove srs assignment circuit
1919
-- Verifier
20-
pure $ verify srs circuit proof y z ys
20+
pure $ verify srs circuit proof rndOracleY rndOracleZ rndOracleYs
2121
where
2222
-- n: Number of multiplication constraints
2323
n = length $ aL assignment

package.yaml

Lines changed: 17 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,6 @@ library:
5353
- Sonic.SRS
5454
- Sonic.Signature
5555
- Sonic.Utils
56-
- Sonic.Curve
5756

5857
executables:
5958
sonic-example:
@@ -73,12 +72,28 @@ executables:
7372
- QuickCheck
7473
tests:
7574
sonic-test:
76-
main: Main.hs
75+
main: Test.Main.hs
7776
source-dirs: test
7877
dependencies:
7978
- sonic
79+
- QuickCheck
8080
- tasty
8181
- tasty-discover
8282
- tasty-hunit
8383
- tasty-quickcheck
84+
85+
benchmarks:
86+
sonic-benchmarks:
87+
source-dirs:
88+
- bench
89+
- test
90+
main: Main.hs
91+
dependencies:
92+
- sonic
93+
- criterion
8494
- QuickCheck
95+
- tasty
96+
- tasty-quickcheck
97+
- tasty-hunit
98+
other-modules:
99+
- Test.Reference

src/Sonic/CommitmentScheme.hs

Lines changed: 10 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -9,17 +9,15 @@ module Sonic.CommitmentScheme
99

1010
import Protolude
1111
import Data.List ((!!))
12-
import Pairing.Pairing (reducedPairing)
12+
import Data.Curve (Curve(..), mul)
13+
import Data.Pairing.BLS12381 (Fr, G1, GT, BLS12381, pairing)
1314
import Math.Polynomial.Laurent
1415
(Laurent, newLaurent, quotLaurent, evalLaurent, expLaurent, coeffsLaurent)
15-
import Curve (Curve(..), Group(..))
16-
1716
import Sonic.SRS (SRS(..))
18-
import Sonic.Curve (Fr, G1, GT)
1917

20-
type Opening f = (f, G1)
18+
type Opening f = (f, G1 BLS12381)
2119

22-
commitPoly :: SRS -> Int -> Laurent Fr -> G1
20+
commitPoly :: SRS -> Int -> Laurent Fr -> G1 BLS12381
2321
commitPoly SRS{..} maxm fX
2422
= foldl' (<>) mempty (negPowers ++ posPowers)
2523
where
@@ -35,7 +33,7 @@ commitPoly SRS{..} maxm fX
3533
negPowers = zipWith mul gNegativeAlphaX (reverse negCoeffs)
3634
posPowers = zipWith mul gPositiveAlphaX posCoeffs
3735

38-
openPoly :: SRS -> G1 -> Fr -> Laurent Fr -> Opening Fr
36+
openPoly :: SRS -> G1 BLS12381 -> Fr -> Laurent Fr -> Opening Fr
3937
openPoly SRS{..} _commitment z fX
4038
= let fz = evalLaurent fX z
4139
wPoly = (fX - newLaurent 0 [fz]) `quotLaurent` newLaurent 0 [-z, 1]
@@ -53,7 +51,7 @@ openPoly SRS{..} _commitment z fX
5351
pcV
5452
:: SRS
5553
-> Int
56-
-> G1
54+
-> G1 BLS12381
5755
-> Fr
5856
-> Opening Fr
5957
-> Bool
@@ -64,7 +62,7 @@ pcV SRS{..} maxm commitment z (v, w)
6462
hxi = if difference >= 0
6563
then hPositiveX !! difference
6664
else hNegativeX !! (abs difference - 1)
67-
eA, eB, eC :: GT
68-
eA = reducedPairing w (hPositiveAlphaX !! 1) -- when i = 1
69-
eB = reducedPairing ((gen `mul` v) <> (w `mul` negate z)) (hPositiveAlphaX !! 0) -- when i = 0
70-
eC = reducedPairing commitment hxi
65+
eA, eB, eC :: GT BLS12381
66+
eA = pairing w (hPositiveAlphaX !! 1) -- when i = 1
67+
eB = pairing ((gen `mul` v) <> (w `mul` negate z)) (hPositiveAlphaX !! 0) -- when i = 0
68+
eC = pairing commitment hxi

src/Sonic/Constraints.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,11 +10,10 @@ module Sonic.Constraints
1010

1111
import Protolude hiding (head)
1212
import Data.List (zipWith4, head, (!!))
13+
import Data.Pairing.BLS12381 (Fr)
1314
import Bulletproofs.ArithmeticCircuit (Assignment(..), GateWeights(..))
1415
import Math.Polynomial.Laurent
1516
(Laurent(..), newLaurent, zeroLaurent, expLaurent)
16-
17-
import Sonic.Curve (Fr)
1817
import Sonic.Utils (BiVariateLaurent, convertToTwoVariateX, convertToTwoVariateY, evalOnY)
1918

2019
rPoly

src/Sonic/Curve.hs

Lines changed: 0 additions & 32 deletions
This file was deleted.

src/Sonic/Protocol.hs

Lines changed: 24 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,44 +1,54 @@
11
-- The interactive Sonic protocol to check that the prover knows a valid assignment of the wires in the circuit
22

33
{-# LANGUAGE RecordWildCards #-}
4+
{-# LANGUAGE DeriveGeneric #-}
5+
{-# LANGUAGE DeriveAnyClass #-}
46
module Sonic.Protocol
57
( Proof
8+
, RndOracle(..)
69
, prove
710
, verify
811
) where
912

1013
import Protolude hiding (head)
1114
import Data.List (head)
15+
import Data.Pairing.BLS12381 (Fr, G1, BLS12381)
1216
import Control.Monad.Random (MonadRandom)
1317
import Bulletproofs.ArithmeticCircuit (ArithCircuit(..), Assignment(..), GateWeights(..))
1418
import Math.Polynomial.Laurent (newLaurent, evalLaurent)
15-
import GaloisField (GaloisField(rnd))
19+
import Data.Field.Galois (rnd)
1620

1721
import Sonic.SRS (SRS(..))
1822
import Sonic.Constraints (rPoly, sPoly, tPoly, kPoly)
1923
import Sonic.CommitmentScheme (commitPoly, openPoly, pcV)
2024
import Sonic.Signature (HscProof(..), hscP, hscV)
2125
import Sonic.Utils (evalOnY)
22-
import Sonic.Curve (Fr, G1)
2326

2427
data Proof f = Proof
25-
{ prR :: G1
26-
, prT :: G1
28+
{ prR :: G1 BLS12381
29+
, prT :: G1 BLS12381
2730
, prA :: f
28-
, prWa :: G1
31+
, prWa :: G1 BLS12381
2932
, prB :: f
30-
, prWb :: G1
31-
, prWt :: G1
33+
, prWb :: G1 BLS12381
34+
, prWt :: G1 BLS12381
3235
, prS :: f
3336
, prHscProof :: HscProof f
34-
}
37+
} deriving (Eq, Show, Generic, NFData)
38+
39+
-- | Values created non-interactively in the random oracle model during proof generation
40+
data RndOracle f = RndOracle
41+
{ rndOracleY :: f
42+
, rndOracleZ :: f
43+
, rndOracleYs :: [f]
44+
} deriving (Eq, Show, Generic, NFData)
3545

3646
prove
3747
:: MonadRandom m
3848
=> SRS
3949
-> Assignment Fr
4050
-> ArithCircuit Fr
41-
-> m (Proof Fr, Fr, Fr, [Fr])
51+
-> m (Proof Fr, RndOracle Fr)
4252
prove srs@SRS{..} assignment@Assignment{..} arithCircuit@ArithCircuit{..} =
4353
if srsD < 7*n
4454
then panic $ "Parameter d is not large enough: " <> show srsD <> " should be greater than " <> show (7*n)
@@ -80,9 +90,11 @@ prove srs@SRS{..} assignment@Assignment{..} arithCircuit@ArithCircuit{..} =
8090
, prS = s
8191
, prHscProof = hscProof
8292
}
83-
, y
84-
, z
85-
, ys
93+
, RndOracle
94+
{ rndOracleY = y
95+
, rndOracleZ = z
96+
, rndOracleYs = ys
97+
}
8698
)
8799
where
88100
n :: Int

src/Sonic/SRS.hs

Lines changed: 12 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -3,22 +3,20 @@
33
module Sonic.SRS where
44

55
import Protolude
6-
import Pairing.Pairing (reducedPairing)
7-
import Curve (Curve(..), Group(..))
8-
9-
import Sonic.Curve (Fr, G1, G2, GT)
6+
import Data.Curve (Curve(..), mul)
7+
import Data.Pairing.BLS12381 (Fr, G1, G2, GT, BLS12381, pairing)
108

119
data SRS = SRS
1210
{ srsD :: Int
13-
, gNegativeX :: [G1]
14-
, gPositiveX :: [G1]
15-
, hNegativeX :: [G2]
16-
, hPositiveX :: [G2]
17-
, gNegativeAlphaX :: [G1]
18-
, gPositiveAlphaX :: [G1]
19-
, hNegativeAlphaX :: [G2]
20-
, hPositiveAlphaX :: [G2]
21-
, srsPairing :: GT
11+
, gNegativeX :: [G1 BLS12381]
12+
, gPositiveX :: [G1 BLS12381]
13+
, hNegativeX :: [G2 BLS12381]
14+
, hPositiveX :: [G2 BLS12381]
15+
, gNegativeAlphaX :: [G1 BLS12381]
16+
, gPositiveAlphaX :: [G1 BLS12381]
17+
, hNegativeAlphaX :: [G2 BLS12381]
18+
, hPositiveAlphaX :: [G2 BLS12381]
19+
, srsPairing :: GT BLS12381
2220
}
2321

2422
-- | Create a new Structured Reference String (SRS)
@@ -38,5 +36,5 @@ new d x alpha
3836
, gPositiveAlphaX = mul gen 0 : (mul gen . ((*) alpha . (^) x) <$> [1..d])
3937
, hNegativeAlphaX = mul gen . ((*) alpha . (^) xInv) <$> [1..d]
4038
, hPositiveAlphaX = mul gen . ((*) alpha . (^) x) <$> [0..d]
41-
, srsPairing = reducedPairing gen (mul gen alpha)
39+
, srsPairing = pairing gen (mul gen alpha)
4240
}

0 commit comments

Comments
 (0)