arithmetic-circuits-0.2.0: Arithmetic circuits for zkSNARKs

Safe HaskellNone
LanguageHaskell2010

Circuit.Arithmetic

Description

Definition of arithmetic circuits: one with a single multiplication gate with affine inputs and another variant with an arbitrary number of such gates.

Synopsis

Documentation

data Gate i f Source #

An arithmetic circuit with a single multiplication gate.

Constructors

Mul 
Equal 

Fields

Split 

Fields

Instances
(Eq f, Eq i) => Eq (Gate i f) Source # 
Instance details

Defined in Circuit.Arithmetic

Methods

(==) :: Gate i f -> Gate i f -> Bool #

(/=) :: Gate i f -> Gate i f -> Bool #

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

Defined in Circuit.Arithmetic

Methods

showsPrec :: Int -> Gate i f -> ShowS #

show :: Gate i f -> String #

showList :: [Gate i f] -> ShowS #

Generic (Gate i f) Source # 
Instance details

Defined in Circuit.Arithmetic

Associated Types

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

Methods

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

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

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

Defined in Circuit.Arithmetic

Methods

toJSON :: Gate i f -> Value #

toEncoding :: Gate i f -> Encoding #

toJSONList :: [Gate i f] -> Value #

toEncodingList :: [Gate i f] -> Encoding #

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

Defined in Circuit.Arithmetic

Methods

parseJSON :: Value -> Parser (Gate i f) #

parseJSONList :: Value -> Parser [Gate i f] #

(NFData f, NFData i) => NFData (Gate i f) Source # 
Instance details

Defined in Circuit.Arithmetic

Methods

rnf :: Gate i f -> () #

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

Defined in Circuit.Arithmetic

Methods

pretty :: Gate i f -> Doc #

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

type Rep (Gate i f) Source # 
Instance details

Defined in Circuit.Arithmetic

mapVarsGate :: (i -> j) -> Gate i f -> Gate j f Source #

Apply mapping to variable names, i.e. rename variables. (Ideally the mapping is injective.)

collectInputsGate :: Ord i => Gate i f -> [i] Source #

outputWires :: Gate i f -> [i] Source #

List output wires of a gate

newtype ArithCircuit f Source #

A circuit is a list of multiplication gates along with their output wire labels (which can be intermediate or actual outputs).

Constructors

ArithCircuit [Gate Wire f] 
Instances
Eq f => Eq (ArithCircuit f) Source # 
Instance details

Defined in Circuit.Arithmetic

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

Defined in Circuit.Arithmetic

Generic (ArithCircuit f) Source # 
Instance details

Defined in Circuit.Arithmetic

Associated Types

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

Methods

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

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

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

Defined in Circuit.Arithmetic

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

Defined in Circuit.Arithmetic

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

Defined in Circuit.Arithmetic

Methods

rnf :: ArithCircuit f -> () #

Show f => Pretty (ArithCircuit f) Source # 
Instance details

Defined in Circuit.Arithmetic

type Rep (ArithCircuit f) Source # 
Instance details

Defined in Circuit.Arithmetic

type Rep (ArithCircuit f) = D1 (MetaData "ArithCircuit" "Circuit.Arithmetic" "arithmetic-circuits-0.2.0-6zOfGRHnhI9W2wAnMDkNU" True) (C1 (MetaCons "ArithCircuit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Gate Wire f])))

generateRoots :: Applicative m => m f -> ArithCircuit f -> m [[f]] Source #

Generate enough roots for a circuit

validArithCircuit :: ArithCircuit f -> Bool Source #

Check whether an arithmetic circuit does not refer to intermediate wires before they are defined and whether output wires are not used as input wires.

data Wire Source #

Wires are can be labeled in the ways given in this data type

Instances
Eq Wire Source # 
Instance details

Defined in Circuit.Arithmetic

Methods

(==) :: Wire -> Wire -> Bool #

(/=) :: Wire -> Wire -> Bool #

Ord Wire Source # 
Instance details

Defined in Circuit.Arithmetic

Methods

compare :: Wire -> Wire -> Ordering #

(<) :: Wire -> Wire -> Bool #

(<=) :: Wire -> Wire -> Bool #

(>) :: Wire -> Wire -> Bool #

(>=) :: Wire -> Wire -> Bool #

max :: Wire -> Wire -> Wire #

min :: Wire -> Wire -> Wire #

Show Wire Source # 
Instance details

Defined in Circuit.Arithmetic

Methods

showsPrec :: Int -> Wire -> ShowS #

show :: Wire -> String #

showList :: [Wire] -> ShowS #

Generic Wire Source # 
Instance details

Defined in Circuit.Arithmetic

Associated Types

type Rep Wire :: Type -> Type #

Methods

from :: Wire -> Rep Wire x #

to :: Rep Wire x -> Wire #

ToJSON Wire Source # 
Instance details

Defined in Circuit.Arithmetic

FromJSON Wire Source # 
Instance details

Defined in Circuit.Arithmetic

NFData Wire Source # 
Instance details

Defined in Circuit.Arithmetic

Methods

rnf :: Wire -> () #

Pretty Wire Source # 
Instance details

Defined in Circuit.Arithmetic

Methods

pretty :: Wire -> Doc #

prettyList :: [Wire] -> Doc #

type Rep Wire Source # 
Instance details

Defined in Circuit.Arithmetic

evalGate Source #

Arguments

:: (Bits f, Fractional f) 
=> (i -> vars -> Maybe f)

lookup a value at a wire

-> (i -> f -> vars -> vars)

update a value at a wire

-> vars

context before evaluation

-> Gate i f

gate

-> vars

context after evaluation

Evaluate a single gate

evalArithCircuit Source #

Arguments

:: (Bits f, Fractional f) 
=> (Wire -> vars -> Maybe f)

lookup a value at a wire

-> (Wire -> f -> vars -> vars)

update a value at a wire

-> ArithCircuit f

circuit to evaluate

-> vars

input variables

-> vars

input and output variables

Evaluate an arithmetic circuit on a given environment containing the inputs. Outputs the entire environment (outputs, intermediate values and inputs).

unsplit Source #

Arguments

:: Num f 
=> [Wire]

(binary) wires containing a binary expansion, small-endian

-> AffineCircuit Wire f 

Turn a binary expansion back into a single value.