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

ZkFold.Symbolic.Data.Class

Synopsis

Documentation

type IsVariable v = (Binary v, NFData v, Ord v) Source #

class (Symbolic (Context x), LayoutFunctor (Layout x), PayloadFunctor (Payload x)) => SymbolicData x where Source #

A class for Symbolic data types.

Minimal complete definition

Nothing

Associated Types

type Context x :: (Type -> Type) -> Type Source #

type Context x = GContext (Rep x)

type Support x :: Type Source #

type Support x = GSupport (Rep x)

type Layout x :: Type -> Type Source #

type Layout x = GLayout (Rep x)

type Payload x :: Type -> Type Source #

type Payload x = GPayload (Rep x)

Methods

arithmetize :: x -> Support x -> Context x (Layout x) Source #

Returns the circuit that makes up x.

default arithmetize :: (Generic x, GSymbolicData (Rep x), Context x ~ GContext (Rep x), Support x ~ GSupport (Rep x), Layout x ~ GLayout (Rep x)) => x -> Support x -> Context x (Layout x) Source #

payload :: x -> Support x -> Payload x (WitnessField (Context x)) Source #

restore :: Context x ~ c => (Support x -> (c (Layout x), Payload x (WitnessField c))) -> x Source #

Restores x from the circuit's outputs.

default restore :: (Context x ~ c, Generic x, GSymbolicData (Rep x), Context x ~ GContext (Rep x), Support x ~ GSupport (Rep x), Layout x ~ GLayout (Rep x), Payload x ~ GPayload (Rep x)) => (Support x -> (c (Layout x), Payload x (WitnessField c))) -> x Source #

Instances

Instances details
SymbolicOutput field => SymbolicData (AffinePoint field) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Associated Types

type Context (AffinePoint field) :: (Type -> Type) -> Type Source #

type Support (AffinePoint field) Source #

type Layout (AffinePoint field) :: Type -> Type Source #

type Payload (AffinePoint field) :: Type -> Type Source #

Methods

arithmetize :: AffinePoint field -> Support (AffinePoint field) -> Context (AffinePoint field) (Layout (AffinePoint field)) Source #

payload :: AffinePoint field -> Support (AffinePoint field) -> Payload (AffinePoint field) (WitnessField (Context (AffinePoint field))) Source #

restore :: Context (AffinePoint field) ~ c => (Support (AffinePoint field) -> (c (Layout (AffinePoint field)), Payload (AffinePoint field) (WitnessField c))) -> AffinePoint field Source #

(SymbolicOutput (BooleanOf field), SymbolicOutput field, Context field ~ Context (BooleanOf field)) => SymbolicData (CompressedPoint field) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Associated Types

type Context (CompressedPoint field) :: (Type -> Type) -> Type Source #

type Support (CompressedPoint field) Source #

type Layout (CompressedPoint field) :: Type -> Type Source #

type Payload (CompressedPoint field) :: Type -> Type Source #

(SymbolicOutput (BooleanOf field), SymbolicOutput field, Context field ~ Context (BooleanOf field)) => SymbolicData (Point field) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Associated Types

type Context (Point field) :: (Type -> Type) -> Type Source #

type Support (Point field) Source #

type Layout (Point field) :: Type -> Type Source #

type Payload (Point field) :: Type -> Type Source #

Methods

arithmetize :: Point field -> Support (Point field) -> Context (Point field) (Layout (Point field)) Source #

payload :: Point field -> Support (Point field) -> Payload (Point field) (WitnessField (Context (Point field))) Source #

restore :: Context (Point field) ~ c => (Support (Point field) -> (c (Layout (Point field)), Payload (Point field) (WitnessField c))) -> Point field Source #

Symbolic c => SymbolicData (Bool c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Bool

Associated Types

type Context (Bool c) :: (Type -> Type) -> Type Source #

type Support (Bool c) Source #

type Layout (Bool c) :: Type -> Type Source #

type Payload (Bool c) :: Type -> Type Source #

Methods

arithmetize :: Bool c -> Support (Bool c) -> Context (Bool c) (Layout (Bool c)) Source #

payload :: Bool c -> Support (Bool c) -> Payload (Bool c) (WitnessField (Context (Bool c))) Source #

restore :: Context (Bool c) ~ c0 => (Support (Bool c) -> (c0 (Layout (Bool c)), Payload (Bool c) (WitnessField c0))) -> Bool c Source #

Symbolic c => SymbolicData (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

Associated Types

type Context (FieldElement c) :: (Type -> Type) -> Type Source #

type Support (FieldElement c) Source #

type Layout (FieldElement c) :: Type -> Type Source #

type Payload (FieldElement c) :: Type -> Type Source #

(SymbolicData (PublicKey 2048 ctx), Symbolic ctx) => SymbolicData (Certificate ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.JWT

Associated Types

type Context (Certificate ctx) :: (Type -> Type) -> Type Source #

type Support (Certificate ctx) Source #

type Layout (Certificate ctx) :: Type -> Type Source #

type Payload (Certificate ctx) :: Type -> Type Source #

Symbolic ctx => SymbolicData (ClientSecret ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.JWT

Associated Types

type Context (ClientSecret ctx) :: (Type -> Type) -> Type Source #

type Support (ClientSecret ctx) Source #

type Layout (ClientSecret ctx) :: Type -> Type Source #

type Payload (ClientSecret ctx) :: Type -> Type Source #

(SymbolicData (PrivateKey 2048 ctx), Symbolic ctx) => SymbolicData (SigningKey ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.JWT

Associated Types

type Context (SigningKey ctx) :: (Type -> Type) -> Type Source #

type Support (SigningKey ctx) Source #

type Layout (SigningKey ctx) :: Type -> Type Source #

type Payload (SigningKey ctx) :: Type -> Type Source #

Symbolic ctx => SymbolicData (TokenHeader ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.JWT

Associated Types

type Context (TokenHeader ctx) :: (Type -> Type) -> Type Source #

type Support (TokenHeader ctx) Source #

type Layout (TokenHeader ctx) :: Type -> Type Source #

type Payload (TokenHeader ctx) :: Type -> Type Source #

Symbolic ctx => SymbolicData (TokenPayload ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.JWT

Associated Types

type Context (TokenPayload ctx) :: (Type -> Type) -> Type Source #

type Support (TokenPayload ctx) Source #

type Layout (TokenPayload ctx) :: Type -> Type Source #

type Payload (TokenPayload ctx) :: Type -> Type Source #

Symbolic c => SymbolicData (Ordering c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

Associated Types

type Context (Ordering c) :: (Type -> Type) -> Type Source #

type Support (Ordering c) Source #

type Layout (Ordering c) :: Type -> Type Source #

type Payload (Ordering c) :: Type -> Type Source #

(Symbolic c, KnownRegisters c 11 'Auto) => SymbolicData (UTCTime c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UTCTime

Associated Types

type Context (UTCTime c) :: (Type -> Type) -> Type Source #

type Support (UTCTime c) Source #

type Layout (UTCTime c) :: Type -> Type Source #

type Payload (UTCTime c) :: Type -> Type Source #

(Symbolic c, LayoutFunctor f) => SymbolicData (c f) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (c f) :: (Type -> Type) -> Type Source #

type Support (c f) Source #

type Layout (c f) :: Type -> Type Source #

type Payload (c f) :: Type -> Type Source #

Methods

arithmetize :: c f -> Support (c f) -> Context (c f) (Layout (c f)) Source #

payload :: c f -> Support (c f) -> Payload (c f) (WitnessField (Context (c f))) Source #

restore :: Context (c f) ~ c0 => (Support (c f) -> (c0 (Layout (c f)), Payload (c f) (WitnessField c0))) -> c f Source #

Symbolic c => SymbolicData (Proxy c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (Proxy c) :: (Type -> Type) -> Type Source #

type Support (Proxy c) Source #

type Layout (Proxy c) :: Type -> Type Source #

type Payload (Proxy c) :: Type -> Type Source #

Methods

arithmetize :: Proxy c -> Support (Proxy c) -> Context (Proxy c) (Layout (Proxy c)) Source #

payload :: Proxy c -> Support (Proxy c) -> Payload (Proxy c) (WitnessField (Context (Proxy c))) Source #

restore :: Context (Proxy c) ~ c0 => (Support (Proxy c) -> (c0 (Layout (Proxy c)), Payload (Proxy c) (WitnessField c0))) -> Proxy c Source #

(SymbolicData x, KnownNat n) => SymbolicData (Vector n x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (Vector n x) :: (Type -> Type) -> Type Source #

type Support (Vector n x) Source #

type Layout (Vector n x) :: Type -> Type Source #

type Payload (Vector n x) :: Type -> Type Source #

Methods

arithmetize :: Vector n x -> Support (Vector n x) -> Context (Vector n x) (Layout (Vector n x)) Source #

payload :: Vector n x -> Support (Vector n x) -> Payload (Vector n x) (WitnessField (Context (Vector n x))) Source #

restore :: Context (Vector n x) ~ c => (Support (Vector n x) -> (c (Layout (Vector n x)), Payload (Vector n x) (WitnessField c))) -> Vector n x Source #

(SymbolicData f, SymbolicData (i f), Context f ~ Context (i f), Support f ~ Support (i f)) => SymbolicData (RecursiveI i f) Source # 
Instance details

Defined in ZkFold.Base.Protocol.IVC.RecursiveFunction

Associated Types

type Context (RecursiveI i f) :: (Type -> Type) -> Type Source #

type Support (RecursiveI i f) Source #

type Layout (RecursiveI i f) :: Type -> Type Source #

type Payload (RecursiveI i f) :: Type -> Type Source #

(Symbolic ctx, KnownRegisters ctx keyLen 'Auto) => SymbolicData (PrivateKey keyLen ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.RSA

Associated Types

type Context (PrivateKey keyLen ctx) :: (Type -> Type) -> Type Source #

type Support (PrivateKey keyLen ctx) Source #

type Layout (PrivateKey keyLen ctx) :: Type -> Type Source #

type Payload (PrivateKey keyLen ctx) :: Type -> Type Source #

Methods

arithmetize :: PrivateKey keyLen ctx -> Support (PrivateKey keyLen ctx) -> Context (PrivateKey keyLen ctx) (Layout (PrivateKey keyLen ctx)) Source #

payload :: PrivateKey keyLen ctx -> Support (PrivateKey keyLen ctx) -> Payload (PrivateKey keyLen ctx) (WitnessField (Context (PrivateKey keyLen ctx))) Source #

restore :: Context (PrivateKey keyLen ctx) ~ c => (Support (PrivateKey keyLen ctx) -> (c (Layout (PrivateKey keyLen ctx)), Payload (PrivateKey keyLen ctx) (WitnessField c))) -> PrivateKey keyLen ctx Source #

(Symbolic ctx, KnownRegisters ctx PubExponentSize 'Auto, KnownRegisters ctx keyLen 'Auto) => SymbolicData (PublicKey keyLen ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.RSA

Associated Types

type Context (PublicKey keyLen ctx) :: (Type -> Type) -> Type Source #

type Support (PublicKey keyLen ctx) Source #

type Layout (PublicKey keyLen ctx) :: Type -> Type Source #

type Payload (PublicKey keyLen ctx) :: Type -> Type Source #

Methods

arithmetize :: PublicKey keyLen ctx -> Support (PublicKey keyLen ctx) -> Context (PublicKey keyLen ctx) (Layout (PublicKey keyLen ctx)) Source #

payload :: PublicKey keyLen ctx -> Support (PublicKey keyLen ctx) -> Payload (PublicKey keyLen ctx) (WitnessField (Context (PublicKey keyLen ctx))) Source #

restore :: Context (PublicKey keyLen ctx) ~ c => (Support (PublicKey keyLen ctx) -> (c (Layout (PublicKey keyLen ctx)), Payload (PublicKey keyLen ctx) (WitnessField c))) -> PublicKey keyLen ctx Source #

(KnownNat n, Symbolic c) => SymbolicData (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Associated Types

type Context (ByteString n c) :: (Type -> Type) -> Type Source #

type Support (ByteString n c) Source #

type Layout (ByteString n c) :: Type -> Type Source #

type Payload (ByteString n c) :: Type -> Type Source #

(SymbolicOutput h, SymbolicOutput a) => SymbolicData (Hash h a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Hash

Associated Types

type Context (Hash h a) :: (Type -> Type) -> Type Source #

type Support (Hash h a) Source #

type Layout (Hash h a) :: Type -> Type Source #

type Payload (Hash h a) :: Type -> Type Source #

Methods

arithmetize :: Hash h a -> Support (Hash h a) -> Context (Hash h a) (Layout (Hash h a)) Source #

payload :: Hash h a -> Support (Hash h a) -> Payload (Hash h a) (WitnessField (Context (Hash h a))) Source #

restore :: Context (Hash h a) ~ c => (Support (Hash h a) -> (c (Layout (Hash h a)), Payload (Hash h a) (WitnessField c))) -> Hash h a Source #

(SymbolicData x, c ~ Context x) => SymbolicData (List c x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.List

Associated Types

type Context (List c x) :: (Type -> Type) -> Type Source #

type Support (List c x) Source #

type Layout (List c x) :: Type -> Type Source #

type Payload (List c x) :: Type -> Type Source #

Methods

arithmetize :: List c x -> Support (List c x) -> Context (List c x) (Layout (List c x)) Source #

payload :: List c x -> Support (List c x) -> Payload (List c x) (WitnessField (Context (List c x))) Source #

restore :: Context (List c x) ~ c0 => (Support (List c x) -> (c0 (Layout (List c x)), Payload (List c x) (WitnessField c0))) -> List c x Source #

(SymbolicOutput x, Context x ~ c) => SymbolicData (Maybe c x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Maybe

Associated Types

type Context (Maybe c x) :: (Type -> Type) -> Type Source #

type Support (Maybe c x) Source #

type Layout (Maybe c x) :: Type -> Type Source #

type Payload (Maybe c x) :: Type -> Type Source #

Methods

arithmetize :: Maybe c x -> Support (Maybe c x) -> Context (Maybe c x) (Layout (Maybe c x)) Source #

payload :: Maybe c x -> Support (Maybe c x) -> Payload (Maybe c x) (WitnessField (Context (Maybe c x))) Source #

restore :: Context (Maybe c x) ~ c0 => (Support (Maybe c x) -> (c0 (Layout (Maybe c x)), Payload (Maybe c x) (WitnessField c0))) -> Maybe c x Source #

(Symbolic c, PayloadFunctor f) => SymbolicData (Payloaded f c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Payloaded

Associated Types

type Context (Payloaded f c) :: (Type -> Type) -> Type Source #

type Support (Payloaded f c) Source #

type Layout (Payloaded f c) :: Type -> Type Source #

type Payload (Payloaded f c) :: Type -> Type Source #

(Symbolic c, SymbolicData x) => SymbolicData (Switch c x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Switch

Associated Types

type Context (Switch c x) :: (Type -> Type) -> Type Source #

type Support (Switch c x) Source #

type Layout (Switch c x) :: Type -> Type Source #

type Payload (Switch c x) :: Type -> Type Source #

Methods

arithmetize :: Switch c x -> Support (Switch c x) -> Context (Switch c x) (Layout (Switch c x)) Source #

payload :: Switch c x -> Support (Switch c x) -> Payload (Switch c x) (WitnessField (Context (Switch c x))) Source #

restore :: Context (Switch c x) ~ c0 => (Support (Switch c x) -> (c0 (Layout (Switch c x)), Payload (Switch c x) (WitnessField c0))) -> Switch c x Source #

(KnownNat n, Symbolic ctx) => SymbolicData (VarByteString n ctx) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.VarByteString

Associated Types

type Context (VarByteString n ctx) :: (Type -> Type) -> Type Source #

type Support (VarByteString n ctx) Source #

type Layout (VarByteString n ctx) :: Type -> Type Source #

type Payload (VarByteString n ctx) :: Type -> Type Source #

(SymbolicData x, SymbolicData y, HApplicative (Context x), Context x ~ Context y, Support x ~ Support y) => SymbolicData (x, y) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (x, y) :: (Type -> Type) -> Type Source #

type Support (x, y) Source #

type Layout (x, y) :: Type -> Type Source #

type Payload (x, y) :: Type -> Type Source #

Methods

arithmetize :: (x, y) -> Support (x, y) -> Context (x, y) (Layout (x, y)) Source #

payload :: (x, y) -> Support (x, y) -> Payload (x, y) (WitnessField (Context (x, y))) Source #

restore :: Context (x, y) ~ c => (Support (x, y) -> (c (Layout (x, y)), Payload (x, y) (WitnessField c))) -> (x, y) Source #

SymbolicData f => SymbolicData (x -> f) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (x -> f) :: (Type -> Type) -> Type Source #

type Support (x -> f) Source #

type Layout (x -> f) :: Type -> Type Source #

type Payload (x -> f) :: Type -> Type Source #

Methods

arithmetize :: (x -> f) -> Support (x -> f) -> Context (x -> f) (Layout (x -> f)) Source #

payload :: (x -> f) -> Support (x -> f) -> Payload (x -> f) (WitnessField (Context (x -> f))) Source #

restore :: Context (x -> f) ~ c => (Support (x -> f) -> (c (Layout (x -> f)), Payload (x -> f) (WitnessField c))) -> x -> f Source #

SymbolicOutput field => SymbolicData (TwistedEdwards curve (AffinePoint field)) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Associated Types

type Context (TwistedEdwards curve (AffinePoint field)) :: (Type -> Type) -> Type Source #

type Support (TwistedEdwards curve (AffinePoint field)) Source #

type Layout (TwistedEdwards curve (AffinePoint field)) :: Type -> Type Source #

type Payload (TwistedEdwards curve (AffinePoint field)) :: Type -> Type Source #

SymbolicEq field => SymbolicData (Weierstrass curve (Point field)) Source # 
Instance details

Defined in ZkFold.Base.Algebra.EllipticCurve.Class

Associated Types

type Context (Weierstrass curve (Point field)) :: (Type -> Type) -> Type Source #

type Support (Weierstrass curve (Point field)) Source #

type Layout (Weierstrass curve (Point field)) :: Type -> Type Source #

type Payload (Weierstrass curve (Point field)) :: Type -> Type Source #

Methods

arithmetize :: Weierstrass curve (Point field) -> Support (Weierstrass curve (Point field)) -> Context (Weierstrass curve (Point field)) (Layout (Weierstrass curve (Point field))) Source #

payload :: Weierstrass curve (Point field) -> Support (Weierstrass curve (Point field)) -> Payload (Weierstrass curve (Point field)) (WitnessField (Context (Weierstrass curve (Point field)))) Source #

restore :: Context (Weierstrass curve (Point field)) ~ c => (Support (Weierstrass curve (Point field)) -> (c (Layout (Weierstrass curve (Point field))), Payload (Weierstrass curve (Point field)) (WitnessField c))) -> Weierstrass curve (Point field) Source #

(Symbolic c, KnownFFA p r c) => SymbolicData (FFA p r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Associated Types

type Context (FFA p r c) :: (Type -> Type) -> Type Source #

type Support (FFA p r c) Source #

type Layout (FFA p r c) :: Type -> Type Source #

type Payload (FFA p r c) :: Type -> Type Source #

Methods

arithmetize :: FFA p r c -> Support (FFA p r c) -> Context (FFA p r c) (Layout (FFA p r c)) Source #

payload :: FFA p r c -> Support (FFA p r c) -> Payload (FFA p r c) (WitnessField (Context (FFA p r c))) Source #

restore :: Context (FFA p r c) ~ c0 => (Support (FFA p r c) -> (c0 (Layout (FFA p r c)), Payload (FFA p r c) (WitnessField c0))) -> FFA p r c Source #

(KnownRegisters c n r, Symbolic c) => SymbolicData (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Associated Types

type Context (UInt n r c) :: (Type -> Type) -> Type Source #

type Support (UInt n r c) Source #

type Layout (UInt n r c) :: Type -> Type Source #

type Payload (UInt n r c) :: Type -> Type Source #

Methods

arithmetize :: UInt n r c -> Support (UInt n r c) -> Context (UInt n r c) (Layout (UInt n r c)) Source #

payload :: UInt n r c -> Support (UInt n r c) -> Payload (UInt n r c) (WitnessField (Context (UInt n r c))) Source #

restore :: Context (UInt n r c) ~ c0 => (Support (UInt n r c) -> (c0 (Layout (UInt n r c)), Payload (UInt n r c) (WitnessField c0))) -> UInt n r c Source #

(SymbolicData x, SymbolicData y, SymbolicData z, HApplicative (Context x), Context x ~ Context y, Context y ~ Context z, Support x ~ Support y, Support y ~ Support z) => SymbolicData (x, y, z) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (x, y, z) :: (Type -> Type) -> Type Source #

type Support (x, y, z) Source #

type Layout (x, y, z) :: Type -> Type Source #

type Payload (x, y, z) :: Type -> Type Source #

Methods

arithmetize :: (x, y, z) -> Support (x, y, z) -> Context (x, y, z) (Layout (x, y, z)) Source #

payload :: (x, y, z) -> Support (x, y, z) -> Payload (x, y, z) (WitnessField (Context (x, y, z))) Source #

restore :: Context (x, y, z) ~ c => (Support (x, y, z) -> (c (Layout (x, y, z)), Payload (x, y, z) (WitnessField c))) -> (x, y, z) Source #

(KnownNat (k - 1), KnownNat k, SymbolicData f, SymbolicData (i f), SymbolicData (c f), Context f ~ Context (c f), Context f ~ Context (i f), Support f ~ Support (c f), Support f ~ Support (i f)) => SymbolicData (AccumulatorInstance k i c f) Source # 
Instance details

Defined in ZkFold.Base.Protocol.IVC.Accumulator

Associated Types

type Context (AccumulatorInstance k i c f) :: (Type -> Type) -> Type Source #

type Support (AccumulatorInstance k i c f) Source #

type Layout (AccumulatorInstance k i c f) :: Type -> Type Source #

type Payload (AccumulatorInstance k i c f) :: Type -> Type Source #

(SymbolicData w, SymbolicData x, SymbolicData y, SymbolicData z, HApplicative (Context x), Context w ~ Context x, Context x ~ Context y, Context y ~ Context z, Support w ~ Support x, Support x ~ Support y, Support y ~ Support z) => SymbolicData (w, x, y, z) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (w, x, y, z) :: (Type -> Type) -> Type Source #

type Support (w, x, y, z) Source #

type Layout (w, x, y, z) :: Type -> Type Source #

type Payload (w, x, y, z) :: Type -> Type Source #

Methods

arithmetize :: (w, x, y, z) -> Support (w, x, y, z) -> Context (w, x, y, z) (Layout (w, x, y, z)) Source #

payload :: (w, x, y, z) -> Support (w, x, y, z) -> Payload (w, x, y, z) (WitnessField (Context (w, x, y, z))) Source #

restore :: Context (w, x, y, z) ~ c => (Support (w, x, y, z) -> (c (Layout (w, x, y, z)), Payload (w, x, y, z) (WitnessField c))) -> (w, x, y, z) Source #

(SymbolicData v, SymbolicData w, SymbolicData x, SymbolicData y, SymbolicData z, HApplicative (Context x), Context v ~ Context w, Context w ~ Context x, Context x ~ Context y, Context y ~ Context z, Support v ~ Support w, Support w ~ Support x, Support x ~ Support y, Support y ~ Support z) => SymbolicData (v, w, x, y, z) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (v, w, x, y, z) :: (Type -> Type) -> Type Source #

type Support (v, w, x, y, z) Source #

type Layout (v, w, x, y, z) :: Type -> Type Source #

type Payload (v, w, x, y, z) :: Type -> Type Source #

Methods

arithmetize :: (v, w, x, y, z) -> Support (v, w, x, y, z) -> Context (v, w, x, y, z) (Layout (v, w, x, y, z)) Source #

payload :: (v, w, x, y, z) -> Support (v, w, x, y, z) -> Payload (v, w, x, y, z) (WitnessField (Context (v, w, x, y, z))) Source #

restore :: Context (v, w, x, y, z) ~ c => (Support (v, w, x, y, z) -> (c (Layout (v, w, x, y, z)), Payload (v, w, x, y, z) (WitnessField c))) -> (v, w, x, y, z) Source #

class (Symbolic (GContext u), Traversable (GLayout u), Representable (GLayout u), Representable (GPayload u)) => GSymbolicData u where Source #

Associated Types

type GContext u :: (Type -> Type) -> Type Source #

type GSupport u :: Type Source #

type GLayout u :: Type -> Type Source #

type GPayload u :: Type -> Type Source #

Methods

garithmetize :: u x -> GSupport u -> GContext u (GLayout u) Source #

gpayload :: u x -> GSupport u -> GPayload u (WitnessField (GContext u)) Source #

grestore :: GContext u ~ c => (GSupport u -> (c (GLayout u), GPayload u (WitnessField c))) -> u x Source #

Instances

Instances details
SymbolicData x => GSymbolicData (Rec0 x :: k -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type GContext (Rec0 x) :: (Type -> Type) -> Type Source #

type GSupport (Rec0 x) Source #

type GLayout (Rec0 x) :: Type -> Type Source #

type GPayload (Rec0 x) :: Type -> Type Source #

Methods

garithmetize :: forall (x0 :: k0). Rec0 x x0 -> GSupport (Rec0 x) -> GContext (Rec0 x) (GLayout (Rec0 x)) Source #

gpayload :: forall (x0 :: k0). Rec0 x x0 -> GSupport (Rec0 x) -> GPayload (Rec0 x) (WitnessField (GContext (Rec0 x))) Source #

grestore :: forall c (x0 :: k0). GContext (Rec0 x) ~ c => (GSupport (Rec0 x) -> (c (GLayout (Rec0 x)), GPayload (Rec0 x) (WitnessField c))) -> Rec0 x x0 Source #

(GSymbolicData u, GSymbolicData v, HApplicative (GContext u), GContext u ~ GContext v, GSupport u ~ GSupport v) => GSymbolicData (u :*: v :: k -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type GContext (u :*: v) :: (Type -> Type) -> Type Source #

type GSupport (u :*: v) Source #

type GLayout (u :*: v) :: Type -> Type Source #

type GPayload (u :*: v) :: Type -> Type Source #

Methods

garithmetize :: forall (x :: k0). (u :*: v) x -> GSupport (u :*: v) -> GContext (u :*: v) (GLayout (u :*: v)) Source #

gpayload :: forall (x :: k0). (u :*: v) x -> GSupport (u :*: v) -> GPayload (u :*: v) (WitnessField (GContext (u :*: v))) Source #

grestore :: forall c (x :: k0). GContext (u :*: v) ~ c => (GSupport (u :*: v) -> (c (GLayout (u :*: v)), GPayload (u :*: v) (WitnessField c))) -> (u :*: v) x Source #

GSymbolicData f => GSymbolicData (M1 i c f :: k -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type GContext (M1 i c f) :: (Type -> Type) -> Type Source #

type GSupport (M1 i c f) Source #

type GLayout (M1 i c f) :: Type -> Type Source #

type GPayload (M1 i c f) :: Type -> Type Source #

Methods

garithmetize :: forall (x :: k0). M1 i c f x -> GSupport (M1 i c f) -> GContext (M1 i c f) (GLayout (M1 i c f)) Source #

gpayload :: forall (x :: k0). M1 i c f x -> GSupport (M1 i c f) -> GPayload (M1 i c f) (WitnessField (GContext (M1 i c f))) Source #

grestore :: forall c0 (x :: k0). GContext (M1 i c f) ~ c0 => (GSupport (M1 i c f) -> (c0 (GLayout (M1 i c f)), GPayload (M1 i c f) (WitnessField c0))) -> M1 i c f x Source #