Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ListItem l p a = ListItem {
- tailHash :: l a
- headLayout :: l a
- headPayload :: p a
- data List c x = List {}
- emptyList :: forall context x. SymbolicData x => Context x ~ context => List context x
- null :: forall context x. Symbolic context => List context x -> Bool context
- (.:) :: forall context x. SymbolicOutput x => Context x ~ context => x -> List context x -> List context x
- hashFun :: MonadCircuit i a w m => i -> i -> i -> m i
- uncons :: forall c x. SymbolicOutput x => Context x ~ c => List c x -> (x, List c x)
- head :: SymbolicOutput x => Context x ~ c => List c x -> x
- tail :: SymbolicOutput x => Context x ~ c => List c x -> List c x
- last :: List context x -> x
- (++) :: List context x -> List context x -> List context x
- filter :: (x -> Bool context) -> List context x -> List context x
- delete :: x -> List context x -> List context x
- (\\) :: List context x -> List context x -> List context x
- singleton :: forall context x. SymbolicOutput x => Context x ~ context => x -> List context x
- (!!) :: List context x -> UInt n Auto context -> x
- concat :: List context (List context x) -> List context x
Documentation
ListItem | |
|
Instances
Generic1 (ListItem l p :: k -> Type) Source # | |
(Representable l, Representable p) => Representable (ListItem l p) Source # | |
(Functor l, Functor p) => Functor (ListItem l p) Source # | |
(Representable l, Representable p) => Distributive (ListItem l p) Source # | |
Defined in ZkFold.Symbolic.Data.List | |
type Rep1 (ListItem l p :: k -> Type) Source # | |
Defined in ZkFold.Symbolic.Data.List type Rep1 (ListItem l p :: k -> Type) = D1 ('MetaData "ListItem" "ZkFold.Symbolic.Data.List" "symbolic-base-0.1.0.0-inplace" 'False) (C1 ('MetaCons "ListItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "tailHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 l) :*: (S1 ('MetaSel ('Just "headLayout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 l) :*: S1 ('MetaSel ('Just "headPayload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 p)))) | |
type Rep (ListItem l p) Source # | |
Defined in ZkFold.Symbolic.Data.List |
Instances
emptyList :: forall context x. SymbolicData x => Context x ~ context => List context x Source #
TODO: A proof-of-concept where hash == id. Replace id with a proper hash if we need lists to be cryptographically secure.
null :: forall context x. Symbolic context => List context x -> Bool context Source #
A list is empty if it's size is 0, in which case the first element of runInvert
is one
.
(.:) :: forall context x. SymbolicOutput x => Context x ~ context => x -> List context x -> List context x infixr 5 Source #
hashFun :: MonadCircuit i a w m => i -> i -> i -> m i Source #
head :: SymbolicOutput x => Context x ~ c => List c x -> x Source #
TODO: Is there really a nicer way to handle empty lists?