Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
ZkFold.Symbolic.Data.Class
Synopsis
- type IsVariable v = (Binary v, NFData v, Ord v)
- type LayoutFunctor f = (Binary1 f, NFData1 f, PayloadFunctor f, Traversable f)
- type PayloadFunctor f = (Representable f, IsVariable (Rep f))
- class (Symbolic (Context x), LayoutFunctor (Layout x), PayloadFunctor (Payload x)) => SymbolicData x where
- type Context x :: (Type -> Type) -> Type
- type Support x :: Type
- type Layout x :: Type -> Type
- type Payload x :: Type -> Type
- arithmetize :: x -> Support x -> Context x (Layout x)
- payload :: x -> Support x -> Payload x (WitnessField (Context x))
- restore :: Context x ~ c => (Support x -> (c (Layout x), Payload x (WitnessField c))) -> x
- type SymbolicOutput x = (SymbolicData x, Support x ~ Proxy (Context x))
- class (Symbolic (GContext u), Traversable (GLayout u), Representable (GLayout u), Representable (GPayload u)) => GSymbolicData u where
- type GContext u :: (Type -> Type) -> Type
- type GSupport u :: Type
- type GLayout u :: Type -> Type
- type GPayload u :: Type -> Type
- garithmetize :: u x -> GSupport u -> GContext u (GLayout u)
- gpayload :: u x -> GSupport u -> GPayload u (WitnessField (GContext u))
- grestore :: GContext u ~ c => (GSupport u -> (c (GLayout u), GPayload u (WitnessField c))) -> u x
Documentation
type LayoutFunctor f = (Binary1 f, NFData1 f, PayloadFunctor f, Traversable f) Source #
type PayloadFunctor f = (Representable f, IsVariable (Rep f)) 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 Support x :: Type Source #
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 #
default payload :: (Generic x, GSymbolicData (Rep x), Context x ~ GContext (Rep x), Support x ~ GSupport (Rep x), Payload x ~ GPayload (Rep x)) => 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.
Instances
type SymbolicOutput x = (SymbolicData x, Support x ~ Proxy (Context x)) 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 #
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
SymbolicData x => GSymbolicData (Rec0 x :: k -> Type) Source # | |
Defined in ZkFold.Symbolic.Data.Class Associated Types type GContext (Rec0 x) :: (Type -> Type) -> Type Source # type GSupport (Rec0 x) 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 # | |
Defined in ZkFold.Symbolic.Data.Class Associated Types type GContext (u :*: v) :: (Type -> Type) -> Type Source # type GSupport (u :*: v) 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 # | |
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 # 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 # |