bulletproofs-0.3.0

Safe HaskellNone
LanguageHaskell2010

Bulletproofs.RangeProof.Internal

Synopsis

Documentation

data RangeProof f Source #

Constructors

RangeProof 

Fields

  • tBlinding :: f

    Blinding factor of the T1 and T2 commitments, combined into the form required to make the committed version of the x-polynomial add up

  • mu :: f

    Blinding factor required for the Verifier to verify commitments A, S

  • t :: f

    Dot product of vectors l and r that prove knowledge of the value in range t = t(x) = l(x) · r(x)

  • aCommit :: Point

    Commitment to aL and aR, where aL and aR are vectors of bits such that aL · 2^n = v and aR = aL − 1^n . A = α · H + aL · G + aR · H

  • sCommit :: Point

    Commitment to new vectors sL, sR, created at random by the Prover

  • t1Commit :: Point

    Pedersen commitment to coefficient t1

  • t2Commit :: Point

    Pedersen commitment to coefficient t2

  • productProof :: InnerProductProof f

    Inner product argument to prove that a commitment P has vectors l, r ∈ Z^n for which P = l · G + r · H + ( l, r ) · U

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

Defined in Bulletproofs.RangeProof.Internal

Methods

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

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

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

Defined in Bulletproofs.RangeProof.Internal

data RangeProofError Source #

Constructors

UpperBoundTooLarge Integer

The upper bound of the range is too large

ValueNotInRange Integer

Value is not within the range required

ValuesNotInRange [Integer]

Values are not within the range required

NNotPowerOf2 Integer

Dimension n is required to be a power of 2

data LRPolys f Source #

Constructors

LRPolys 

Fields

  • l0 :: [f]
     
  • l1 :: [f]
     
  • r0 :: [f]
     
  • r1 :: [f]
     

data TPoly f Source #

Constructors

TPoly 

Fields

encodeBit :: (AsInteger f, Num f) => Integer -> f -> [f] Source #

Encode the value v into a bit representation. Let aL be a vector of bits such that 2^n = v (put more simply, the components of a L are the binary digits of v).

reversedEncodeBit :: (AsInteger f, Num f) => Integer -> f -> [f] Source #

Bits of v reversed. v = 2^n = a_0 * 2^0 + ... + a_n-1 * 2^(n-1)

reversedEncodeBitMulti :: (AsInteger f, Num f) => Integer -> [f] -> [f] Source #

complementaryVector :: Num a => [a] -> [a] Source #

In order to prove that v is in range, each element of aL is either 0 or 1. We construct a “complementary” vector aR = aL − 1^n and require that aL ◦ aR = 0 hold.

fillWithZeros :: Num f => Integer -> [f] -> [f] Source #

Add non-relevant zeros to a vector to match the size of the other vectors used in the protocol

obfuscateEncodedBits :: (Eq f, Field f) => Integer -> [f] -> [f] -> f -> f -> f Source #

Obfuscate encoded bits with challenges y and z. z^2 * 2^n + z * − 1^n − aR, y^n + aR · y^n = (z^2) * v The property holds because − 1^n − aR, y^n = 0 and · aR, y^n = 0

obfuscateEncodedBitsSingle :: (Eq f, Field f) => Integer -> [f] -> [f] -> f -> f -> f Source #

commitBitVectors :: (MonadRandom m, AsInteger f) => f -> f -> [f] -> [f] -> [f] -> [f] -> m (Point, Point) Source #

We need to blind the vectors aL, aR to make the proof zero knowledge. The Prover creates randomly vectors sL and sR. On creating these, the Prover can send commitments to these vectors; these are properly blinded vector Pedersen commitments:

delta :: (Eq f, Field f) => Integer -> Integer -> f -> f -> f Source #

(z − z^2) * y^n − z^3 * 2^n

checkRange :: Integer -> Integer -> Bool Source #

Check that a value is in a specific range

checkRanges :: Integer -> [Integer] -> Bool Source #

Check that a value is in a specific range

computeLRCommitment :: (AsInteger f, Eq f, Num f, Show f) => Integer -> Integer -> Point -> Point -> f -> f -> f -> f -> f -> f -> [Point] -> Point Source #

Compute commitment of linear vector polynomials l and r P = A + xS − zG + (z*y^n + z^2 * 2^n) * hs'