bulletproofs-1.0.1

Safe HaskellNone
LanguageHaskell2010

Bulletproofs.RangeProof

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

Generic (RangeProof f) Source # 
Instance details

Defined in Bulletproofs.RangeProof.Internal

Associated Types

type Rep (RangeProof f) :: Type -> Type #

Methods

from :: RangeProof f -> Rep (RangeProof f) x #

to :: Rep (RangeProof f) x -> RangeProof f #

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

Defined in Bulletproofs.RangeProof.Internal

Methods

rnf :: RangeProof f -> () #

type Rep (RangeProof f) Source # 
Instance details

Defined in Bulletproofs.RangeProof.Internal

data RangeProofError f Source #

Constructors

UpperBoundTooLarge Integer

The upper bound of the range is too large

ValueNotInRange f

Value is not within the range required

ValuesNotInRange [f]

Values are not within the range required

NNotPowerOf2 Integer

Dimension n is required to be a power of 2

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

Defined in Bulletproofs.RangeProof.Internal

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

Defined in Bulletproofs.RangeProof.Internal

Generic (RangeProofError f) Source # 
Instance details

Defined in Bulletproofs.RangeProof.Internal

Associated Types

type Rep (RangeProofError f) :: Type -> Type #

NFData f => NFData (RangeProofError f) Source # 
Instance details

Defined in Bulletproofs.RangeProof.Internal

Methods

rnf :: RangeProofError f -> () #

type Rep (RangeProofError f) Source # 
Instance details

Defined in Bulletproofs.RangeProof.Internal

generateProof Source #

Arguments

:: (KnownNat p, MonadRandom m) 
=> Integer

Upper bound of the range we want to prove

-> (PrimeField p, PrimeField p)

Values we want to prove in range and their blinding factors

-> ExceptT (RangeProofError (PrimeField p)) m (RangeProof (PrimeField p)) 

Prove that a value lies in a specific range

generateProofUnsafe Source #

Arguments

:: (KnownNat p, MonadRandom m) 
=> Integer

Upper bound of the range we want to prove

-> (PrimeField p, PrimeField p)

Values we want to prove in range and their blinding factors

-> m (RangeProof (PrimeField p)) 

Generate range proof from valid inputs

verifyProof Source #

Arguments

:: KnownNat p 
=> Integer

Range upper bound

-> Point

Commitments of in-range values

-> RangeProof (PrimeField p)

Proof that a secret committed value lies in a certain interval

-> Bool 

Verify that a commitment was computed from a value in a given range