Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Ring f => AlgebraicMap f i (d :: Natural) a where
- algebraicMap :: a -> i f -> Vector k [f] -> Vector (k - 1) f -> f -> [f]
- padDecomposition :: forall f n. (MultiplicativeMonoid f, AdditiveMonoid f, KnownNat n) => f -> Vector n [f] -> [f]
- degreeDecomposition :: forall f d v. KnownNat (d + 1) => [Poly f v Natural] -> Vector (d + 1) [Poly f v Natural]
- deg :: Mono v Natural -> Natural
Documentation
class Ring f => AlgebraicMap f i (d :: Natural) a where Source #
Algebraic map of a
.
It calculates a system of equations defining a
in some way.
The inputs are polymorphic in a ring element f
.
The main application is to define the verifier's algebraic map in the NARK protocol.
:: a | |
-> i f | public input |
-> Vector k [f] | NARK proof witness (the list of prover messages) |
-> Vector (k - 1) f | Verifier random challenges |
-> f | Slack variable for padding |
-> [f] |
the algebraic map Vsps computed by the NARK verifier.
Instances
(Ring f, Representable i, KnownNat (d + 1), Arithmetic a, Scale a f) => AlgebraicMap f i d (ArithmetizableFunction a i p) Source # | |
Defined in ZkFold.Base.Protocol.Protostar.AlgebraicMap algebraicMap :: forall (k :: Natural). ArithmetizableFunction a i p -> i f -> Vector k [f] -> Vector (k - 1) f -> f -> [f] Source # |
padDecomposition :: forall f n. (MultiplicativeMonoid f, AdditiveMonoid f, KnownNat n) => f -> Vector n [f] -> [f] Source #