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

ZkFold.Base.Protocol.Commitment.KZG

Synopsis

Documentation

newtype KZG c1 c2 t f (d :: Natural) Source #

d is the degree of polynomials in the protocol

Constructors

KZG f 

Instances

Instances details
Arbitrary f => Arbitrary (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

Methods

arbitrary :: Gen (KZG c1 c2 t f d) #

shrink :: KZG c1 c2 t f d -> [KZG c1 c2 t f d] #

Show f => Show (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

Methods

showsPrec :: Int -> KZG c1 c2 t f d -> ShowS #

show :: KZG c1 c2 t f d -> String #

showList :: [KZG c1 c2 t f d] -> ShowS #

Eq f => Eq (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

Methods

(==) :: KZG c1 c2 t f d -> KZG c1 c2 t f d -> Bool #

(/=) :: KZG c1 c2 t f d -> KZG c1 c2 t f d -> Bool #

(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 #

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

Defined in ZkFold.Base.Protocol.Commitment.KZG

type Input (KZG c1 c2 t f d) = Map f (Vector (Point c1), Vector f)
type Proof (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

type Proof (KZG c1 c2 t f d) = Map f (Point c1)
type Setup (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

type Setup (KZG c1 c2 t f d) = (Vector (Point c1), Point c2, Point c2)
type Transcript (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

type Transcript (KZG c1 c2 t f d) = ByteString
type Witness (KZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

type Witness (KZG c1 c2 t f d) = WitnessKZG c1 c2 t f d

newtype WitnessKZG c1 c2 t f d Source #

Constructors

WitnessKZG 

Fields

Instances

Instances details
(EllipticCurve c1, f ~ ScalarField c1, KnownNat d, Ring f, Arbitrary f, Ord f) => Arbitrary (WitnessKZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

Methods

arbitrary :: Gen (WitnessKZG c1 c2 t f d) #

shrink :: WitnessKZG c1 c2 t f d -> [WitnessKZG c1 c2 t f d] #

(EllipticCurve c1, f ~ ScalarField c1, Show f) => Show (WitnessKZG c1 c2 t f d) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Commitment.KZG

Methods

showsPrec :: Int -> WitnessKZG c1 c2 t f d -> ShowS #

show :: WitnessKZG c1 c2 t f d -> String #

showList :: [WitnessKZG c1 c2 t f d] -> ShowS #

provePolyVecEval :: forall size f. (KnownNat size, FiniteField f, Eq f) => PolyVec f size -> f -> PolyVec f size Source #

com :: (EllipticCurve curve, f ~ ScalarField curve) => Vector (Point curve) -> PolyVec f size -> Point curve Source #