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

ZkFold.Symbolic.Data.Class

Synopsis

Documentation

data SomeData c where Source #

Constructors

SomeData :: (Typeable t, SymbolicData t, Context t ~ c) => t -> SomeData c 

class SymbolicData x where Source #

A class for Symbolic data types.

Associated Types

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

type Support x :: Type Source #

type Layout x :: Type -> Type Source #

Methods

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

Returns the circuit that makes up x.

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

Restores x from the circuit's outputs.

Instances

Instances details
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 #

Methods

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

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

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 #

SymbolicData a => SymbolicData (Lexicographical a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

Associated Types

type Context (Lexicographical a) :: (Type -> Type) -> Type Source #

type Support (Lexicographical a) Source #

type Layout (Lexicographical a) :: Type -> Type Source #

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 #

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 #

Methods

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

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

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

Methods

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

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

(Symbolic c, BaseField c ~ a) => SymbolicData (Point (Ed25519 c)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

Associated Types

type Context (Point (Ed25519 c)) :: (Type -> Type) -> Type Source #

type Support (Point (Ed25519 c)) Source #

type Layout (Point (Ed25519 c)) :: Type -> Type Source #

(SymbolicData x, Package (Context 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 #

Methods

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

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

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 #

SymbolicData (FFA p c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FFA

Associated Types

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

type Support (FFA p c) Source #

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

Methods

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

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

(HApplicative c, SymbolicData x, Context x ~ c, Support x ~ Proxy 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 #

Methods

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

restore :: (Support (Maybe c x) -> Context (Maybe c x) (Layout (Maybe c x))) -> Maybe c x 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 #

Methods

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

restore :: (Support (x, y) -> Context (x, y) (Layout (x, y))) -> (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 #

Methods

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

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

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 #

Methods

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

restore :: (Support (UInt n r c) -> Context (UInt n r c) (Layout (UInt n r c))) -> 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 #

Methods

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

restore :: (Support (x, y, z) -> Context (x, y, z) (Layout (x, y, z))) -> (x, y, z) 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 #

Methods

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

restore :: (Support (w, x, y, z) -> Context (w, x, y, z) (Layout (w, x, y, z))) -> (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 #

Methods

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

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