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

ZkFold.Base.Protocol.NonInteractiveProof

Documentation

class Monoid t => ToTranscript t a where Source #

Methods

toTranscript :: a -> t Source #

Instances

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

Defined in ZkFold.Base.Protocol.NonInteractiveProof

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

class Monoid t => FromTranscript t a where Source #

Methods

newTranscript :: t -> t Source #

fromTranscript :: t -> a Source #

challenge :: forall t a. FromTranscript t a => t -> (a, t) Source #

challenges :: FromTranscript t a => t -> Natural -> ([a], t) Source #

class NonInteractiveProof a where Source #

Associated Types

type Transcript a Source #

type Setup a Source #

type Witness a Source #

type Input a Source #

type Proof a Source #

Methods

setup :: a -> Setup a Source #

prove :: Setup a -> Witness a -> (Input a, Proof a) Source #

verify :: Setup a -> Input a -> Proof a -> Bool Source #

Instances

Instances details
(KnownNat d, KnownNat (PlonkPermutationSize d), KnownNat (PlonkMaxPolyDegree d), ToTranscript t F, ToTranscript t G1, FromTranscript t F) => NonInteractiveProof (Plonk d t) Source # 
Instance details

Defined in ZkFold.Base.Protocol.ARK.Plonk

Associated Types

type Transcript (Plonk d t) Source #

type Setup (Plonk d t) Source #

type Witness (Plonk d t) Source #

type Input (Plonk d t) Source #

type Proof (Plonk d t) Source #

Methods

setup :: Plonk d t -> Setup (Plonk d t) Source #

prove :: Setup (Plonk d t) -> Witness (Plonk d t) -> (Input (Plonk d t), Proof (Plonk d t)) Source #

verify :: Setup (Plonk d t) -> Input (Plonk d t) -> Proof (Plonk d t) -> Bool Source #

(f ~ ScalarField c1, f ~ ScalarField c2, Pairing c1 c2 t, Binary f, KnownNat d, KZG c1 c2 t f d ~ kzg, Num f, Ord f, Ring f, Finite f, Field f, AdditiveGroup (BaseField c1), Binary (BaseField c1)) => NonInteractiveProof (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

Associated Types

type Transcript (KZG c1 c2 t f d) Source #

type Setup (KZG c1 c2 t f d) Source #

type Witness (KZG c1 c2 t f d) Source #

type Input (KZG c1 c2 t f d) Source #

type Proof (KZG c1 c2 t f d) Source #

Methods

setup :: KZG c1 c2 t f d -> Setup (KZG c1 c2 t f d) Source #

prove :: Setup (KZG c1 c2 t f d) -> Witness (KZG c1 c2 t f d) -> (Input (KZG c1 c2 t f d), Proof (KZG c1 c2 t f d)) Source #

verify :: Setup (KZG c1 c2 t f d) -> Input (KZG c1 c2 t f d) -> Proof (KZG c1 c2 t f d) -> Bool Source #

data ProveAPIResult Source #

Instances

Instances details
Generic ProveAPIResult Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof

Associated Types

type Rep ProveAPIResult :: Type -> Type #

Show ProveAPIResult Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof

NFData ProveAPIResult Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof

Methods

rnf :: ProveAPIResult -> () #

Eq ProveAPIResult Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof

type Rep ProveAPIResult Source # 
Instance details

Defined in ZkFold.Base.Protocol.NonInteractiveProof

type Rep ProveAPIResult = D1 ('MetaData "ProveAPIResult" "ZkFold.Base.Protocol.NonInteractiveProof" "zkfold-base-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ProveAPISuccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: (C1 ('MetaCons "ProveAPIErrorSetup" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProveAPIErrorWitness" 'PrefixI 'False) (U1 :: Type -> Type)))