Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Stack zipping.
This module provides functions for flattening stacks into tuples.
Also here we define an instance which turns any instruction, not only lambdas, into a valid value.
Synopsis
- class KnownIsoT (ZippedStack s) => ZipInstr (s :: [Type]) where
- type ZippedStack s :: Type
- zipInstrTyped :: Instr (ToTs s) '[ToT (ZippedStack s)]
- unzipInstrTyped :: Instr '[ToT (ZippedStack s)] (ToTs s)
- zipInstr :: forall s. ZipInstr s => s :-> '[ZippedStack s]
- unzipInstr :: forall s. ZipInstr s => '[ZippedStack s] :-> s
- type ZipInstrs ss = Each '[ZipInstr] ss
- zippingStack :: ZipInstrs [inp, out] => (inp :-> out) -> Fn (ZippedStack inp) (ZippedStack out)
- unzippingStack :: ZipInstrs [inp, out] => Fn (ZippedStack inp) (ZippedStack out) -> inp :-> out
- data ZippedStackRepr a b = a ::: b
- data ZSNil = ZSNil
Documentation
class KnownIsoT (ZippedStack s) => ZipInstr (s :: [Type]) where Source #
Zipping stack into tuple and back.
type ZippedStack s :: Type Source #
A type which contains the whole stack zipped.
zipInstrTyped :: Instr (ToTs s) '[ToT (ZippedStack s)] Source #
Fold given stack into single value in typed Michelson.
unzipInstrTyped :: Instr '[ToT (ZippedStack s)] (ToTs s) Source #
Unfold given stack from a single value in typed Michelson.
Instances
ZipInstr ('[] :: [Type]) Source # | |
Defined in Lorentz.Zip type ZippedStack '[] Source # zipInstrTyped :: Instr (ToTs '[]) '[ToT (ZippedStack '[])] Source # unzipInstrTyped :: Instr '[ToT (ZippedStack '[])] (ToTs '[]) Source # | |
(ZipInstr (b ': s), KnownIsoT a) => ZipInstr (a ': (b ': s)) Source # | Such definition seems the only possible one we can support efficiently. |
Defined in Lorentz.Zip type ZippedStack (a ': (b ': s)) Source # zipInstrTyped :: Instr (ToTs (a ': (b ': s))) '[ToT (ZippedStack (a ': (b ': s)))] Source # unzipInstrTyped :: Instr '[ToT (ZippedStack (a ': (b ': s)))] (ToTs (a ': (b ': s))) Source # | |
KnownIsoT a => ZipInstr '[a] Source # | |
Defined in Lorentz.Zip type ZippedStack '[a] Source # zipInstrTyped :: Instr (ToTs '[a]) '[ToT (ZippedStack '[a])] Source # unzipInstrTyped :: Instr '[ToT (ZippedStack '[a])] (ToTs '[a]) Source # |
zipInstr :: forall s. ZipInstr s => s :-> '[ZippedStack s] Source #
Fold given stack into single value.
unzipInstr :: forall s. ZipInstr s => '[ZippedStack s] :-> s Source #
Unfold given stack from a single value.
type ZipInstrs ss = Each '[ZipInstr] ss Source #
Require several stacks to comply ZipInstr
constraint.
zippingStack :: ZipInstrs [inp, out] => (inp :-> out) -> Fn (ZippedStack inp) (ZippedStack out) Source #
Flatten both ends of instruction stack.
unzippingStack :: ZipInstrs [inp, out] => Fn (ZippedStack inp) (ZippedStack out) -> inp :-> out Source #
Unflatten both ends of instruction stack.
data ZippedStackRepr a b Source #
A type used to represent a zipped stack of at least two elements, isomorphic to a pair and represented as such in Michelson.
a ::: b infixr 5 |
Instances
A type used to represent an empty zipped stack, isomorphic to a unit and represented as such in Michelson.
Orphan instances
(HasAnnotation (ZippedStack i), HasAnnotation (ZippedStack o)) => HasAnnotation (i :-> o) Source # | |
getAnnotation :: FollowEntrypointFlag -> Notes (ToT (i :-> o)) Source # | |
HasRPCRepr (inp :-> out) Source # | |
type AsRPC (inp :-> out) | |
(WellTypedToT (ZippedStack inp), WellTypedToT (ZippedStack out), ZipInstr inp, ZipInstr out) => IsoValue (inp :-> out) Source # | |