Safe Haskell | None |
---|---|
Language | Haskell2010 |
Definition of arithmetic circuits: one with a single multiplication gate with affine inputs and another variant with an arbitrary number of such gates.
Synopsis
- data Gate i f
- = Mul {
- mulLeft :: AffineCircuit i f
- mulRight :: AffineCircuit i f
- mulOutput :: i
- | Equal { }
- | Split {
- splitInput :: i
- splitOutputs :: [i]
- = Mul {
- mapVarsGate :: (i -> j) -> Gate i f -> Gate j f
- collectInputsGate :: Ord i => Gate i f -> [i]
- outputWires :: Gate i f -> [i]
- newtype ArithCircuit f = ArithCircuit [Gate Wire f]
- fetchVars :: AffineCircuit Wire f -> [Wire]
- generateRoots :: Applicative m => m f -> ArithCircuit f -> m [[f]]
- validArithCircuit :: ArithCircuit f -> Bool
- data Wire
- evalGate :: (Bits f, Fractional f) => (i -> vars -> Maybe f) -> (i -> f -> vars -> vars) -> vars -> Gate i f -> vars
- evalArithCircuit :: forall f vars. (Bits f, Fractional f) => (Wire -> vars -> Maybe f) -> (Wire -> f -> vars -> vars) -> ArithCircuit f -> vars -> vars
- unsplit :: Num f => [Wire] -> AffineCircuit Wire f
Documentation
An arithmetic circuit with a single multiplication gate.
Mul | |
| |
Equal | |
Split | |
|
Instances
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).
ArithCircuit [Gate Wire f] |
Instances
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.
Wires are can be labeled in the ways given in this data type
Instances
Eq Wire Source # | |
Ord Wire Source # | |
Show Wire Source # | |
Generic Wire Source # | |
ToJSON Wire Source # | |
Defined in Circuit.Arithmetic | |
FromJSON Wire Source # | |
NFData Wire Source # | |
Defined in Circuit.Arithmetic | |
Pretty Wire Source # | |
Defined in Circuit.Arithmetic | |
type Rep Wire Source # | |
Defined in Circuit.Arithmetic type Rep Wire = D1 (MetaData "Wire" "Circuit.Arithmetic" "arithmetic-circuits-0.2.0-6zOfGRHnhI9W2wAnMDkNU" False) (C1 (MetaCons "InputWire" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)) :+: (C1 (MetaCons "IntermediateWire" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "OutputWire" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)))) |
:: (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
:: (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).