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

ZkFold.Base.Protocol.Plonk

Synopsis

Documentation

data Plonk p i (n :: Natural) l curve1 curve2 transcript Source #

Constructors

Plonk 

Fields

Instances

Instances details
(NonInteractiveProof (Plonkup p i n l c1 c2 ts) core, SetupProve (Plonkup p i n l c1 c2 ts) ~ PlonkupProverSetup p i n l c1 c2, SetupVerify (Plonkup p i n l c1 c2 ts) ~ PlonkupVerifierSetup p i n l c1 c2, Witness (Plonkup p i n l c1 c2 ts) ~ (PlonkupWitnessInput p i c1, PlonkupProverSecret c1), Input (Plonkup p i n l c1 c2 ts) ~ PlonkupInput l c1, Proof (Plonkup p i n l c1 c2 ts) ~ PlonkupProof c1, KnownNat n, Foldable l, Ord (BooleanOf c1) (BaseField c1), AdditiveGroup (BaseField c1), Pairing c1 c2, Arithmetic (ScalarField c1), ToTranscript ts Word8, ToTranscript ts (ScalarField c1), ToTranscript ts (CompressedPoint c1), FromTranscript ts (ScalarField c1), CoreFunction c1 core) => NonInteractiveProof (Plonk p i n l c1 c2 ts) (core :: k) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

Associated Types

type Transcript (Plonk p i n l c1 c2 ts) Source #

type SetupProve (Plonk p i n l c1 c2 ts) Source #

type SetupVerify (Plonk p i n l c1 c2 ts) Source #

type Witness (Plonk p i n l c1 c2 ts) Source #

type Input (Plonk p i n l c1 c2 ts) Source #

type Proof (Plonk p i n l c1 c2 ts) Source #

Methods

setupProve :: Plonk p i n l c1 c2 ts -> SetupProve (Plonk p i n l c1 c2 ts) Source #

setupVerify :: Plonk p i n l c1 c2 ts -> SetupVerify (Plonk p i n l c1 c2 ts) Source #

prove :: SetupProve (Plonk p i n l c1 c2 ts) -> Witness (Plonk p i n l c1 c2 ts) -> (Input (Plonk p i n l c1 c2 ts), Proof (Plonk p i n l c1 c2 ts)) Source #

verify :: SetupVerify (Plonk p i n l c1 c2 ts) -> Input (Plonk p i n l c1 c2 ts) -> Proof (Plonk p i n l c1 c2 ts) -> Bool Source #

(Arithmetic (ScalarField c1), Binary (ScalarField c1), Binary (Rep p), Binary (Rep i), Ord (Rep i), Arbitrary (Plonkup p i n l c1 c2 t)) => Arbitrary (Plonk p i n l c1 c2 t) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

Methods

arbitrary :: Gen (Plonk p i n l c1 c2 t) #

shrink :: Plonk p i n l c1 c2 t -> [Plonk p i n l c1 c2 t] #

(Show1 l, Show (Rep i), Show (ScalarField c1), Ord (Rep i)) => Show (Plonk p i n l c1 c2 t) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

Methods

showsPrec :: Int -> Plonk p i n l c1 c2 t -> ShowS #

show :: Plonk p i n l c1 c2 t -> String #

showList :: [Plonk p i n l c1 c2 t] -> ShowS #

type Input (Plonk p i n l c1 c2 ts) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

type Input (Plonk p i n l c1 c2 ts) = PlonkupInput l c1
type Proof (Plonk p i n l c1 c2 ts) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

type Proof (Plonk p i n l c1 c2 ts) = PlonkupProof c1
type SetupProve (Plonk p i n l c1 c2 ts) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

type SetupProve (Plonk p i n l c1 c2 ts) = PlonkupProverSetup p i n l c1 c2
type SetupVerify (Plonk p i n l c1 c2 ts) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

type SetupVerify (Plonk p i n l c1 c2 ts) = PlonkupVerifierSetup p i n l c1 c2
type Transcript (Plonk p i n l c1 c2 ts) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

type Transcript (Plonk p i n l c1 c2 ts) = ts
type Witness (Plonk p i n l c1 c2 ts) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

type Witness (Plonk p i n l c1 c2 ts) = (PlonkupWitnessInput p i c1, PlonkupProverSecret c1)