bulletproofs-1.1.0

Safe HaskellNone
LanguageHaskell2010

Bulletproofs.RangeProof

Synopsis

Documentation

data RangeProof f p 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 :: p

    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 :: p

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

  • t1Commit :: p

    Pedersen commitment to coefficient t1

  • t2Commit :: p

    Pedersen commitment to coefficient t2

  • productProof :: InnerProductProof f p

    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 p) => Eq (RangeProof f p) Source # 
Instance details

Defined in Bulletproofs.RangeProof.Internal

Methods

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

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

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

Defined in Bulletproofs.RangeProof.Internal

Methods

showsPrec :: Int -> RangeProof f p -> ShowS #

show :: RangeProof f p -> String #

showList :: [RangeProof f p] -> ShowS #

Generic (RangeProof f p) Source # 
Instance details

Defined in Bulletproofs.RangeProof.Internal

Associated Types

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

Methods

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

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

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

Defined in Bulletproofs.RangeProof.Internal

Methods

rnf :: RangeProof f p -> () #

type Rep (RangeProof f p) 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

:: MonadRandom m 
=> Integer

Upper bound of the range we want to prove

-> (Fr, Fr)

Values we want to prove in range and their blinding factors

-> ExceptT (RangeProofError Fr) m (RangeProof Fr PA) 

Prove that a value lies in a specific range

generateProofUnsafe Source #

Arguments

:: MonadRandom m 
=> Integer

Upper bound of the range we want to prove

-> (Fr, Fr)

Values we want to prove in range and their blinding factors

-> m (RangeProof Fr PA) 

Generate range proof from valid inputs

verifyProof Source #

Arguments

:: Integer

Range upper bound

-> PA

Commitments of in-range values

-> RangeProof Fr PA

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