Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class AccumulatorScheme i f c m ctx a where
- prover :: a -> f -> Accumulator i f c m -> InstanceProofPair i c m -> (Accumulator i f c m, [c])
- verifier :: i -> [c] -> AccumulatorInstance i f c -> AccumulatorInstance i f c -> [c] -> Bool ctx
- decider :: a -> (f, KeyScale f) -> Accumulator i f c m -> Bool ctx
- data KeyScale f = KeyScale f f
- class LinearCombination a b where
- linearCombination :: a -> a -> b
- class LinearCombinationWith a b where
- linearCombinationWith :: a -> b -> b -> b
Documentation
class AccumulatorScheme i f c m ctx a where Source #
Accumulator scheme for V_NARK as described in Chapter 3.4 of the Protostar paper
prover :: a -> f -> Accumulator i f c m -> InstanceProofPair i c m -> (Accumulator i f c m, [c]) Source #
verifier :: i -> [c] -> AccumulatorInstance i f c -> AccumulatorInstance i f c -> [c] -> Bool ctx Source #
decider :: a -> (f, KeyScale f) -> Accumulator i f c m -> Bool ctx Source #
Instances
KeyScale f f |
Instances
Generic (KeyScale f) Source # | |
Show f => Show (KeyScale f) Source # | |
NFData f => NFData (KeyScale f) Source # | |
type Rep (KeyScale f) Source # | |
Defined in ZkFold.Base.Protocol.Protostar.AccumulatorScheme type Rep (KeyScale f) = D1 ('MetaData "KeyScale" "ZkFold.Base.Protocol.Protostar.AccumulatorScheme" "symbolic-base-0.1.0.0-inplace" 'False) (C1 ('MetaCons "KeyScale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f))) |
class LinearCombination a b where Source #
Class describing types which can form a polynomial linear combination: linearCombination a1 a2 -> a1 * X + a2
linearCombination :: a -> a -> b Source #
Instances
(Ring a, Ord key, KnownNat k) => LinearCombination (Map key a) (Map key (PolyVec a k)) Source # | |
Defined in ZkFold.Base.Protocol.Protostar.Fold | |
(Ring a, KnownNat n, KnownNat k) => LinearCombination (Vector n a) (Vector n (PolyVec a k)) Source # | |
Defined in ZkFold.Base.Protocol.Protostar.Fold |
class LinearCombinationWith a b where Source #
Same as above, but with a coefficient known at runtime linearCombination coeff b1 b2 -> b1 * coeff + b2
linearCombinationWith :: a -> b -> b -> b Source #
Instances
(Scale f a, AdditiveSemigroup a) => LinearCombinationWith f [a] Source # | |
Defined in ZkFold.Base.Protocol.Protostar.AccumulatorScheme linearCombinationWith :: f -> [a] -> [a] -> [a] Source # | |
(Ring a, KnownNat n) => LinearCombinationWith a (Vector n a) Source # | |
Defined in ZkFold.Base.Protocol.Protostar.Fold |