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

ZkFold.Base.Protocol.NonInteractiveProof.Internal

Documentation

class Monoid ts => ToTranscript ts a where Source #

Methods

toTranscript :: a -> ts Source #

Instances

Instances details
Binary a => ToTranscript ByteString a Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof.Internal

transcript :: ToTranscript ts a => ts -> a -> ts Source #

class Monoid ts => FromTranscript ts a where Source #

Methods

fromTranscript :: ts -> a Source #

Instances

Instances details
Binary a => FromTranscript ByteString a Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof.Internal

challenge :: forall ts a. FromTranscript ts a => ts -> a Source #

challenges :: (ToTranscript ts Word8, FromTranscript ts a) => ts -> Natural -> ([a], ts) Source #

class NonInteractiveProof a core where Source #

Associated Types

type Transcript a Source #

type SetupProve a Source #

type SetupVerify a Source #

type Witness a Source #

type Input a Source #

type Proof a Source #

Instances

Instances details
(KZG g1 g2 d ~ kzg, KnownNat d, Ord f, Binary f, FiniteField f, AdditiveGroup f, f ~ ScalarFieldOf g1, Binary g1, Pairing g1 g2 gt, Eq gt, CoreFunction g1 core) => NonInteractiveProof (KZG g1 g2 d) (core :: k) Source # 
Instance details

Defined in ZkFold.Base.Protocol.KZG

Associated Types

type Transcript (KZG g1 g2 d) Source #

type SetupProve (KZG g1 g2 d) Source #

type SetupVerify (KZG g1 g2 d) Source #

type Witness (KZG g1 g2 d) Source #

type Input (KZG g1 g2 d) Source #

type Proof (KZG g1 g2 d) Source #

Methods

setupProve :: KZG g1 g2 d -> SetupProve (KZG g1 g2 d) Source #

setupVerify :: KZG g1 g2 d -> SetupVerify (KZG g1 g2 d) Source #

prove :: SetupProve (KZG g1 g2 d) -> Witness (KZG g1 g2 d) -> (Input (KZG g1 g2 d), Proof (KZG g1 g2 d)) Source #

verify :: SetupVerify (KZG g1 g2 d) -> Input (KZG g1 g2 d) -> Proof (KZG g1 g2 d) -> Bool Source #

(NonInteractiveProof (Plonkup p i n l g1 g2 ts) core, SetupProve (Plonkup p i n l g1 g2 ts) ~ PlonkupProverSetup p i n l g1 g2, SetupVerify (Plonkup p i n l g1 g2 ts) ~ PlonkupVerifierSetup p i n l g1 g2, Witness (Plonkup p i n l g1 g2 ts) ~ (PlonkupWitnessInput p i g1, PlonkupProverSecret g1), Input (Plonkup p i n l g1 g2 ts) ~ PlonkupInput l g1, Proof (Plonkup p i n l g1 g2 ts) ~ PlonkupProof g1, KnownNat n, Foldable l, Compressible g1, Pairing g1 g2 gt, Eq gt, Arithmetic (ScalarFieldOf g1), ToTranscript ts Word8, ToTranscript ts (ScalarFieldOf g1), ToTranscript ts (Compressed g1), FromTranscript ts (ScalarFieldOf g1), CoreFunction g1 core) => NonInteractiveProof (Plonk p i n l g1 g2 ts) (core :: k) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Plonk

Associated Types

type Transcript (Plonk p i n l g1 g2 ts) Source #

type SetupProve (Plonk p i n l g1 g2 ts) Source #

type SetupVerify (Plonk p i n l g1 g2 ts) Source #

type Witness (Plonk p i n l g1 g2 ts) Source #

type Input (Plonk p i n l g1 g2 ts) Source #

type Proof (Plonk p i n l g1 g2 ts) Source #

Methods

setupProve :: Plonk p i n l g1 g2 ts -> SetupProve (Plonk p i n l g1 g2 ts) Source #

setupVerify :: Plonk p i n l g1 g2 ts -> SetupVerify (Plonk p i n l g1 g2 ts) Source #

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

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

(KnownNat n, Representable p, Representable i, Representable l, Foldable l, Ord (Rep i), Pairing g1 g2 gt, Compressible g1, Eq gt, Arithmetic (ScalarFieldOf g1), Binary (ScalarFieldOf g2), ToTranscript ts Word8, ToTranscript ts (ScalarFieldOf g1), ToTranscript ts (Compressed g1), FromTranscript ts (ScalarFieldOf g1), CoreFunction g1 core) => NonInteractiveProof (Plonkup p i n l g1 g2 ts) (core :: k) Source #

Based on the paper https://eprint.iacr.org/2022/086.pdf

Instance details

Defined in ZkFold.Base.Protocol.Plonkup

Associated Types

type Transcript (Plonkup p i n l g1 g2 ts) Source #

type SetupProve (Plonkup p i n l g1 g2 ts) Source #

type SetupVerify (Plonkup p i n l g1 g2 ts) Source #

type Witness (Plonkup p i n l g1 g2 ts) Source #

type Input (Plonkup p i n l g1 g2 ts) Source #

type Proof (Plonkup p i n l g1 g2 ts) Source #

Methods

setupProve :: Plonkup p i n l g1 g2 ts -> SetupProve (Plonkup p i n l g1 g2 ts) Source #

setupVerify :: Plonkup p i n l g1 g2 ts -> SetupVerify (Plonkup p i n l g1 g2 ts) Source #

prove :: SetupProve (Plonkup p i n l g1 g2 ts) -> Witness (Plonkup p i n l g1 g2 ts) -> (Input (Plonkup p i n l g1 g2 ts), Proof (Plonkup p i n l g1 g2 ts)) Source #

verify :: SetupVerify (Plonkup p i n l g1 g2 ts) -> Input (Plonkup p i n l g1 g2 ts) -> Proof (Plonkup p i n l g1 g2 ts) -> Bool Source #

class CyclicGroup g => CoreFunction g core where Source #

Methods

msm :: f ~ ScalarFieldOf g => Vector g -> PolyVec f size -> g Source #

polyMul :: (f ~ ScalarFieldOf g, Field f, Eq f) => Poly f -> Poly f -> Poly f Source #

Instances

Instances details
(CyclicGroup g, f ~ ScalarFieldOf g) => CoreFunction g HaskellCore Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof.Internal

Methods

msm :: forall f (size :: Natural). f ~ ScalarFieldOf g => Vector g -> PolyVec f size -> g Source #

polyMul :: (f ~ ScalarFieldOf g, Field f, Eq f) => Poly f -> Poly f -> Poly f Source #

data HaskellCore Source #

Instances

Instances details
(CyclicGroup g, f ~ ScalarFieldOf g) => CoreFunction g HaskellCore Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof.Internal

Methods

msm :: forall f (size :: Natural). f ~ ScalarFieldOf g => Vector g -> PolyVec f size -> g Source #

polyMul :: (f ~ ScalarFieldOf g, Field f, Eq f) => Poly f -> Poly f -> Poly f Source #