arithmetic-circuits-0.2.0: Arithmetic circuits for zkSNARKs

Safe HaskellNone
LanguageHaskell2010

Circuit.Bulletproofs

Description

Translate arithmetic circuits into a Hadamard product equation and linear constraints.

Synopsis

Documentation

data SetupProof f p Source #

Constructors

SetupProof 

Fields

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

Defined in Circuit.Bulletproofs

Methods

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

show :: SetupProof f p -> String #

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

Generic (SetupProof f p) Source # 
Instance details

Defined in Circuit.Bulletproofs

Associated Types

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

Methods

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

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

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

Defined in Circuit.Bulletproofs

Methods

rnf :: SetupProof f p -> () #

type Rep (SetupProof f p) Source # 
Instance details

Defined in Circuit.Bulletproofs

type Rep (SetupProof f p)

data AltArithCircuit f Source #

Instances
Show f => Show (AltArithCircuit f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Generic (AltArithCircuit f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Associated Types

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

ToJSON f => ToJSON (AltArithCircuit f) Source # 
Instance details

Defined in Circuit.Bulletproofs

FromJSON f => FromJSON (AltArithCircuit f) Source # 
Instance details

Defined in Circuit.Bulletproofs

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

Defined in Circuit.Bulletproofs

Methods

rnf :: AltArithCircuit f -> () #

(Pretty f, Show f) => Pretty (AltArithCircuit f) Source # 
Instance details

Defined in Circuit.Bulletproofs

type Rep (AltArithCircuit f) Source # 
Instance details

Defined in Circuit.Bulletproofs

data LinearConstraint f Source #

Instances
Show f => Show (LinearConstraint f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Generic (LinearConstraint f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Associated Types

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

ToJSON f => ToJSON (LinearConstraint f) Source # 
Instance details

Defined in Circuit.Bulletproofs

FromJSON f => FromJSON (LinearConstraint f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Pretty f => Pretty (LinearConstraint f) Source # 
Instance details

Defined in Circuit.Bulletproofs

type Rep (LinearConstraint f) Source # 
Instance details

Defined in Circuit.Bulletproofs

type Rep (LinearConstraint f) = D1 (MetaData "LinearConstraint" "Circuit.Bulletproofs" "arithmetic-circuits-0.2.0-6zOfGRHnhI9W2wAnMDkNU" False) (C1 (MetaCons "LinearConstraint" PrefixI True) ((S1 (MetaSel (Just "lcWeightsLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int f)) :*: S1 (MetaSel (Just "lcWeightsRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int f))) :*: (S1 (MetaSel (Just "lcWeightsOut") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int f)) :*: (S1 (MetaSel (Just "lcWeightsIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int f)) :*: S1 (MetaSel (Just "lcConstant") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 f)))))

data GateConstraint i f Source #

Instances
(Show f, Show i) => Show (GateConstraint i f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Generic (GateConstraint i f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Associated Types

type Rep (GateConstraint i f) :: Type -> Type #

Methods

from :: GateConstraint i f -> Rep (GateConstraint i f) x #

to :: Rep (GateConstraint i f) x -> GateConstraint i f #

(ToJSON i, ToJSON f) => ToJSON (GateConstraint i f) Source # 
Instance details

Defined in Circuit.Bulletproofs

(FromJSON f, FromJSON i) => FromJSON (GateConstraint i f) Source # 
Instance details

Defined in Circuit.Bulletproofs

(Pretty i, Pretty f) => Pretty (GateConstraint i f) Source # 
Instance details

Defined in Circuit.Bulletproofs

Methods

pretty :: GateConstraint i f -> Doc #

prettyList :: [GateConstraint i f] -> Doc #

type Rep (GateConstraint i f) Source # 
Instance details

Defined in Circuit.Bulletproofs

type Rep (GateConstraint i f)

rewire :: Int -> Wire -> AltWire Source #

rewireCircuit :: ArithCircuit f -> AltArithCircuit f Source #

Use different wire type as required for the constraints generated in this module.

transformInputs :: forall f. Num f => AltArithCircuit f -> AltArithCircuit f Source #

Replace all input wires v_i with a mul-gate (v_i * 1). This means that when we translate it to linear constraints, the weights matrix for V will always be of rank m, where m is the number of input wires, as is required by the Bulletproof protocol.

evalCircuit Source #

Arguments

:: Num f 
=> AltArithCircuit f

circuit to evaluate

-> Assignment f

initial context (containing input variables)

-> Assignment f

input and output variables