bulletproofs-0.4.0

Safe HaskellNone
LanguageHaskell2010

Bulletproofs.InnerProductProof

Synopsis

Documentation

generateProof Source #

Arguments

:: (AsInteger f, Eq f, Field f) 
=> InnerProductBase

Generators Gs, Hs, h

-> Point

Commitment P = A + xS − zG + (z*y^n + z^2 * 2^n) * hs' of vectors l and r whose inner product is t

-> InnerProductWitness f

Vectors l and r that hide bit vectors aL and aR, respectively

-> InnerProductProof f 

Generate proof that a witness l, r satisfies the inner product relation on public input (Gs, Hs, h)

verifyProof Source #

Arguments

:: (AsInteger f, Field f) 
=> Integer

Range upper bound

-> InnerProductBase

Generators Gs, Hs, h

-> Point

Commitment P

-> InnerProductProof f

Proof that a secret committed value lies in a certain interval

-> Bool 

Optimized non-interactive verifier using multi-exponentiation and batch verification

data InnerProductProof f Source #

Constructors

InnerProductProof 

Fields

  • lCommits :: [Point]

    Vector of commitments of the elements in the original vector l whose size is the logarithm of base 2 of the size of vector l

  • rCommits :: [Point]

    Vector of commitments of the elements in the original vector r whose size is the logarithm of base 2 of the size of vector r

  • l :: f

    Remaining element of vector l at the end of the recursive algorithm that generates the inner-product proof

  • r :: f

    Remaining element of vector r at the end of the recursive algorithm that generates the inner-product proof

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

Defined in Bulletproofs.InnerProductProof.Internal

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

Defined in Bulletproofs.InnerProductProof.Internal

Generic (InnerProductProof f) Source # 
Instance details

Defined in Bulletproofs.InnerProductProof.Internal

Associated Types

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

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

Defined in Bulletproofs.InnerProductProof.Internal

Methods

rnf :: InnerProductProof f -> () #

type Rep (InnerProductProof f) Source # 
Instance details

Defined in Bulletproofs.InnerProductProof.Internal

type Rep (InnerProductProof f) = D1 (MetaData "InnerProductProof" "Bulletproofs.InnerProductProof.Internal" "bulletproofs-0.4.0-BbsVKuGWdW83BsRx9JvgG9" False) (C1 (MetaCons "InnerProductProof" PrefixI True) ((S1 (MetaSel (Just "lCommits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point]) :*: S1 (MetaSel (Just "rCommits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Point])) :*: (S1 (MetaSel (Just "l") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 f) :*: S1 (MetaSel (Just "r") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 f))))

data InnerProductBase Source #

Constructors

InnerProductBase 

Fields

  • bGs :: [Point]

    Independent generator Gs ∈ G^n

  • bHs :: [Point]

    Independent generator Hs ∈ G^n

  • bH :: Point

    Internally fixed group element H ∈ G for which there is no known discrete-log relation among Gs, Hs, bG

data InnerProductWitness f Source #

Constructors

InnerProductWitness 

Fields

  • ls :: [f]

    Vector of values l that the prover uses to compute lCommits in the recursive inner product algorithm

  • rs :: [f]

    Vector of values r that the prover uses to compute rCommits in the recursive inner product algorithm