symbolic-base-0.1.0.0: ZkFold Symbolic compiler and zero-knowledge proof protocols
Safe HaskellSafe-Inferred
LanguageHaskell2010

ZkFold.Base.Protocol.Protostar.SpecialSound

Synopsis

Documentation

class SpecialSoundProtocol f a where Source #

Associated Types

type Witness f a Source #

type Input f a Source #

type ProverMessage f a Source #

type VerifierMessage f a Source #

type VerifierOutput f a Source #

type Degree a :: Natural Source #

d in the paper, the verifier degree

Methods

outputLength :: a -> Natural Source #

l in the paper, the number of algebraic equations checked by the verifier

rounds :: a -> Natural Source #

k in the paper

prover :: a -> Witness f a -> Input f a -> SpecialSoundTranscript f a -> ProverMessage f a Source #

verifier :: a -> Input f a -> [ProverMessage f a] -> [f] -> VerifierOutput f a Source #

Instances

Instances details
(Arithmetic f, KnownNat n) => SpecialSoundProtocol f (ProtostarPermutation n) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.Permutation

(Arithmetic f, KnownNat l, KnownNat sizeT) => SpecialSoundProtocol f (ProtostarLookup l sizeT) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.Lookup

Associated Types

type Witness f (ProtostarLookup l sizeT) Source #

type Input f (ProtostarLookup l sizeT) Source #

type ProverMessage f (ProtostarLookup l sizeT) Source #

type VerifierMessage f (ProtostarLookup l sizeT) Source #

type VerifierOutput f (ProtostarLookup l sizeT) Source #

type Degree (ProtostarLookup l sizeT) :: Natural Source #

(SpecialSoundProtocol f a, BoolType (VerifierOutput f a), Eq (VerifierOutput f a) [c], m ~ ProverMessage f a) => SpecialSoundProtocol f (CommitOpen m c a) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.CommitOpen

Associated Types

type Witness f (CommitOpen m c a) Source #

type Input f (CommitOpen m c a) Source #

type ProverMessage f (CommitOpen m c a) Source #

type VerifierMessage f (CommitOpen m c a) Source #

type VerifierOutput f (CommitOpen m c a) Source #

type Degree (CommitOpen m c a) :: Natural Source #

Methods

outputLength :: CommitOpen m c a -> Natural Source #

rounds :: CommitOpen m c a -> Natural Source #

prover :: CommitOpen m c a -> Witness f (CommitOpen m c a) -> Input f (CommitOpen m c a) -> SpecialSoundTranscript f (CommitOpen m c a) -> ProverMessage f (CommitOpen m c a) Source #

verifier :: CommitOpen m c a -> Input f (CommitOpen m c a) -> [ProverMessage f (CommitOpen m c a)] -> [f] -> VerifierOutput f (CommitOpen m c a) Source #

(Arithmetic f, KnownNat m, KnownNat n) => SpecialSoundProtocol f (ProtostarGate m n c d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.Gate

Associated Types

type Witness f (ProtostarGate m n c d) Source #

type Input f (ProtostarGate m n c d) Source #

type ProverMessage f (ProtostarGate m n c d) Source #

type VerifierMessage f (ProtostarGate m n c d) Source #

type VerifierOutput f (ProtostarGate m n c d) Source #

type Degree (ProtostarGate m n c d) :: Natural Source #

Methods

outputLength :: ProtostarGate m n c d -> Natural Source #

rounds :: ProtostarGate m n c d -> Natural Source #

prover :: ProtostarGate m n c d -> Witness f (ProtostarGate m n c d) -> Input f (ProtostarGate m n c d) -> SpecialSoundTranscript f (ProtostarGate m n c d) -> ProverMessage f (ProtostarGate m n c d) Source #

verifier :: ProtostarGate m n c d -> Input f (ProtostarGate m n c d) -> [ProverMessage f (ProtostarGate m n c d)] -> [f] -> VerifierOutput f (ProtostarGate m n c d) Source #

(Arithmetic a, Symbolic ctx, FromConstant a (BaseField ctx), Scale a (BaseField ctx)) => SpecialSoundProtocol (FieldElement ctx) (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

class AlgebraicMap f a where Source #

Algebraic map is a much more versatile and powerful tool when used separatey from SpecialSoundProtocol. It calculates a system of equations [f] defining a in some way. If f is a number or a field element, then the result is a vector of polynomial values. However, f can be a polynomial, in which case the result will be a system of polynomials. This polymorphism is exploited in the AccumulatorScheme prover.

Associated Types

type MapInput f a Source #

type MapMessage f a Source #

Methods

algebraicMap Source #

Arguments

:: a 
-> MapInput f a

public input

-> [MapMessage f a]

NARK proof witness (the list of prover messages)

-> [f]

Verifier random challenges

-> f

Slack variable for padding

-> [f] 

the algebraic map V_sps computed by the verifier.

Instances

Instances details
(Arithmetic f, KnownNat n) => AlgebraicMap f (ProtostarPermutation n) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.Permutation

(AlgebraicMap f a, m ~ MapMessage f a) => AlgebraicMap f (CommitOpen m c a) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.CommitOpen

Associated Types

type MapInput f (CommitOpen m c a) Source #

type MapMessage f (CommitOpen m c a) Source #

Methods

algebraicMap :: CommitOpen m c a -> MapInput f (CommitOpen m c a) -> [MapMessage f (CommitOpen m c a)] -> [f] -> f -> [f] Source #

(Arithmetic a, Scale a f, MultiplicativeMonoid f, Exponent f Natural, AdditiveMonoid f) => AlgebraicMap f (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

Associated Types

type MapInput f (ArithmeticCircuit a (Vector n) o) Source #

type MapMessage f (ArithmeticCircuit a (Vector n) o) Source #

Methods

algebraicMap :: ArithmeticCircuit a (Vector n) o -> MapInput f (ArithmeticCircuit a (Vector n) o) -> [MapMessage f (ArithmeticCircuit a (Vector n) o)] -> [f] -> f -> [f] Source #

(Arithmetic f, KnownNat m, KnownNat n) => AlgebraicMap f (ProtostarGate m n c d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.Gate

Associated Types

type MapInput f (ProtostarGate m n c d) Source #

type MapMessage f (ProtostarGate m n c d) Source #

Methods

algebraicMap :: ProtostarGate m n c d -> MapInput f (ProtostarGate m n c d) -> [MapMessage f (ProtostarGate m n c d)] -> [f] -> f -> [f] Source #