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

ZkFold.Base.Data.Package

Synopsis

Documentation

class HFunctor c => Package c where Source #

A Package is a higher-order functor (HFunctor) which allows to (un)pack layered structures of nested functors.

Minimal complete definition

(unpack | unpackWith), (pack | packWith)

Methods

unpack :: Functor f => c (f :.: g) -> f (c g) Source #

Unpacks the outer layer of a package. Note that it is almost always better to define unpackWith instead and rely on the default implementation of unpack. The following should hold:

Definition
unpack p == unpackWith unComp1 p

unpackWith :: Functor f => (forall a. h a -> f (g a)) -> c h -> f (c g) Source #

Given a way to peel the outer layer, unpacks it. If unpack is specified instead, a default definition is available. The following should hold:

Definition
unpackWith f p == unpack (hmap (Comp1 . f) p)
Compatibility
hmap f p == unPar1 (unpackWith (Par1 . f) p)

pack :: (Foldable f, Functor f) => f (c g) -> c (f :.: g) Source #

Packs the outer layer into the package. Note that it is almost always better to define packWith instead and rely on the default implementation of pack. The following should hold:

Definition
pack p == packWith Comp1 p
Inverse
pack (unpack p) == p

packWith :: (Foldable f, Functor f) => (forall a. f (g a) -> h a) -> f (c g) -> c h Source #

Given a way to merge the outer layer, packs it. If pack is specified instead, a default definition if available. The following should hold:

Definition
packWith f p == hmap (f . unComp1) (pack p)
Compatibility
hmap f p == packWith (f . unPar1) (Par1 p)

Instances

Instances details
Package (Interpreter a :: (k1 -> Type) -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Interpreter

Methods

unpack :: forall f (g :: k10 -> Type). Functor f => Interpreter a (f :.: g) -> f (Interpreter a g) Source #

unpackWith :: Functor f => (forall (a0 :: k10). h a0 -> f (g a0)) -> Interpreter a h -> f (Interpreter a g) Source #

pack :: forall f (g :: k10 -> Type). (Foldable f, Functor f) => f (Interpreter a g) -> Interpreter a (f :.: g) Source #

packWith :: (Foldable f, Functor f) => (forall (a0 :: k10). f (g a0) -> h a0) -> f (Interpreter a g) -> Interpreter a h Source #

(Ord (Rep i), Ord a) => Package (ArithmeticCircuit a p i :: (Type -> Type) -> Type) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Internal

Methods

unpack :: forall f (g :: k1 -> Type). Functor f => ArithmeticCircuit a p i (f :.: g) -> f (ArithmeticCircuit a p i g) Source #

unpackWith :: Functor f => (forall (a0 :: k1). h a0 -> f (g a0)) -> ArithmeticCircuit a p i h -> f (ArithmeticCircuit a p i g) Source #

pack :: forall f (g :: k1 -> Type). (Foldable f, Functor f) => f (ArithmeticCircuit a p i g) -> ArithmeticCircuit a p i (f :.: g) Source #

packWith :: (Foldable f, Functor f) => (forall (a0 :: k1). f (g a0) -> h a0) -> f (ArithmeticCircuit a p i g) -> ArithmeticCircuit a p i h Source #

unpacked :: (Package c, Functor f) => c f -> f (c Par1) Source #

Performs the full unpacking.

packed :: (Package c, Foldable f, Functor f) => f (c Par1) -> c f Source #

Performs the full package.