| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Morley.Michelson.Typed.Util
Description
General-purpose utility functions for typed types.
Synopsis
- data DfsSettings m = DfsSettings {}
- data CtorEffectsApp m = CtorEffectsApp {}
- ceaBottomToTop :: CtorEffectsApp x
- dfsTraverseInstr :: forall m inp out. Monad m => DfsSettings m -> (forall i o. Instr i o -> m (Instr i o)) -> Instr inp out -> m (Instr inp out)
- dfsInstr :: forall x inp out. Monoid x => DfsSettings (Writer x) -> (forall i o. Instr i o -> (Instr i o, x)) -> Instr inp out -> (Instr inp out, x)
- dfsFoldInstr :: forall x inp out. Monoid x => DfsSettings (Writer x) -> (forall i o. Instr i o -> x) -> Instr inp out -> x
- dfsModifyInstr :: DfsSettings Identity -> (forall i o. Instr i o -> Instr i o) -> Instr inp out -> Instr inp out
- isMichelsonInstr :: Instr i o -> Bool
- linearizeLeft :: Instr inp out -> Instr inp out
- linearizeLeftDeep :: Instr inp out -> Instr inp out
- dfsFoldMapValue :: Monoid x => (forall t'. Value t' -> x) -> Value t -> x
- dfsFoldMapValueM :: (Monoid x, Monad m) => (forall t'. Value t' -> m x) -> Value t -> m x
- dfsMapValue :: forall t. (forall t'. Value t' -> Value t') -> Value t -> Value t
- dfsTraverseValue :: forall t m. Monad m => (forall t'. Value t' -> m (Value t')) -> Value t -> m (Value t)
- isStringValue :: Value t -> Maybe MText
- isBytesValue :: Value t -> Maybe ByteString
- allAtomicValues :: forall t a. (forall t'. Value t' -> Maybe a) -> Value t -> [a]
- data PushableStorageSplit s st where
- ConstantStorage :: ConstantScope st => Value st -> PushableStorageSplit s st
- PushableValueStorage :: StorageScope st => Instr s (st ': s) -> PushableStorageSplit s st
- PartlyPushableStorage :: (StorageScope heavy, StorageScope st) => Value heavy -> Instr (heavy ': s) (st ': s) -> PushableStorageSplit s st
- splitPushableStorage :: StorageScope t => Value t -> PushableStorageSplit s t
- analyzeInstrFailure :: HasCallStack => Instr i o -> RemFail Instr i o
Instruction analysis
data DfsSettings m Source #
Options for dfsTraverseInstr family of functions.
Constructors
| DfsSettings | |
Fields
| |
Instances
| Default (DfsSettings x) Source # | |
Defined in Morley.Michelson.Typed.Util Methods def :: DfsSettings x # | |
data CtorEffectsApp m Source #
Describes how intermediate nodes in instruction tree are accounted.
Constructors
| CtorEffectsApp | |
Fields
| |
Instances
| Buildable (CtorEffectsApp x) Source # | |
Defined in Morley.Michelson.Typed.Util Methods build :: CtorEffectsApp x -> Builder # | |
ceaBottomToTop :: CtorEffectsApp x Source #
Deprecated: "Bottom to top" is the only available behaviour now.
Gather effects first for children nodes, then for their parents.
dfsTraverseInstr :: forall m inp out. Monad m => DfsSettings m -> (forall i o. Instr i o -> m (Instr i o)) -> Instr inp out -> m (Instr inp out) Source #
Traverse a typed instruction in depth-first order.
The step action will be applied in bottom-to-top order, i.e. first to the children of a node, then to the node itself.
dfsInstr :: forall x inp out. Monoid x => DfsSettings (Writer x) -> (forall i o. Instr i o -> (Instr i o, x)) -> Instr inp out -> (Instr inp out, x) Source #
Deprecated: Use dfsModifyInstr, dfsFoldInstr or dfsTraverseInstr instead.
Traverse a typed instruction in depth-first order.
<> is used to concatenate intermediate results.
Each instructions can be changed using the supplied step function.
It does not consider extra instructions (not present in Michelson).
dfsFoldInstr :: forall x inp out. Monoid x => DfsSettings (Writer x) -> (forall i o. Instr i o -> x) -> Instr inp out -> x Source #
Specialization of dfsTraverseInstr for case when changing the instruction is
not required.
dfsModifyInstr :: DfsSettings Identity -> (forall i o. Instr i o -> Instr i o) -> Instr inp out -> Instr inp out Source #
Specialization of dfsTraverseInstr which only modifies given instruction.
isMichelsonInstr :: Instr i o -> Bool Source #
Whether this instruction is a real Michelson instruction.
Only the root is in question, children in the instruction tree are not accounted for.
>>>isMichelsonInstr (Seq Nop Nop)True
>>>isMichelsonInstr (Ext $ COMMENT_ITEM "comment")False
This function is helpful e.g. in debugger.
Changing instruction tree structure
linearizeLeft :: Instr inp out -> Instr inp out Source #
There are many ways to represent a sequence of more than 2 instructions.
E. g. for i1; i2; i3 it can be Seq i1 $ Seq i2 i3 or Seq (Seq i1 i2) i3.
This function enforces a particular structure. Specifically, it makes each
Seq have a single instruction (i. e. not Seq) in its second argument.
This function also erases redundant Nops.
Please note that this function is not recursive, it does not
linearize contents of IF and similar instructions.
linearizeLeftDeep :: Instr inp out -> Instr inp out Source #
"Deep" version of linearizeLeft. It recursively linearizes
instructions stored in other instructions.
Value analysis
dfsFoldMapValue :: Monoid x => (forall t'. Value t' -> x) -> Value t -> x Source #
Specialization of dfsMapValue for case when changing the value is
not required.
dfsFoldMapValueM :: (Monoid x, Monad m) => (forall t'. Value t' -> m x) -> Value t -> m x Source #
Specialization of dfsMapValue for case when changing the value is
not required.
dfsMapValue :: forall t. (forall t'. Value t' -> Value t') -> Value t -> Value t Source #
Traverse a value in depth-first order.
dfsTraverseValue :: forall t m. Monad m => (forall t'. Value t' -> m (Value t')) -> Value t -> m (Value t) Source #
Traverse a value in depth-first order.
isBytesValue :: Value t -> Maybe ByteString Source #
If value is a bytestring, return the stored bytestring.
allAtomicValues :: forall t a. (forall t'. Value t' -> Maybe a) -> Value t -> [a] Source #
Takes a selector which checks whether a value can be converted to something. Recursively applies it to all values. Collects extracted values in a list.
Instruction generation
data PushableStorageSplit s st where Source #
Result of splitting a storage Value of st on the stack s.
The idea behind this is to either: prove that the whole Value can be put on
the stack without containing a single big_map or to split it into:
a Value containing its big_maps and an instruction to reconstruct the
storage.
The main idea behind this is to create a large storage in Michelson code to
then create a contract using CREATE_CONTRACT.
Note: a simpler solution would have been to replace big_map Values with
an EMPTY_BIG_MAP followed by many UPDATE to push its content, but sadly
a bug (tezostezos1154) prevents this from being done.
Constructors
| ConstantStorage :: ConstantScope st => Value st -> PushableStorageSplit s st | The type of the storage is fully constant. |
| PushableValueStorage :: StorageScope st => Instr s (st ': s) -> PushableStorageSplit s st | The type of the storage is not a constant, but its value does not contain
|
| PartlyPushableStorage :: (StorageScope heavy, StorageScope st) => Value heavy -> Instr (heavy ': s) (st ': s) -> PushableStorageSplit s st | The type of the storage and part of its value (here |
splitPushableStorage :: StorageScope t => Value t -> PushableStorageSplit s t Source #
Splits the given storage Value into a PushableStorageSplit.
This is based off the fact that the only storages that cannot be directly
PUSHed are the ones that contain BigMaps and tickets.
See difference between StorageScope and ConstantScope.
So what we do here is to create a Value as small as possible with all the
big_maps in it (if any) and an Instr that can use it to rebuild the original
storage Value.
Note: This is done this way to avoid using EMPTY_BIG_MAP instructions, see
PushableStorageSplit for motivation.
Working with RemFail
analyzeInstrFailure :: HasCallStack => Instr i o -> RemFail Instr i o Source #
Check whether instruction fails at each execution path or have at least one non-failing path.
This function assumes that given instruction contains no dead code (contract with dead code cannot be valid Michelson contract) and may behave in unexpected way if such is present. Term "dead code" includes instructions which render into empty Michelson, like Morley extensions. On the other hand, this function does not traverse the whole instruction tree; performs fastest on left-growing combs.
Often we already have information about instruction failure, use this function only in cases when this info is actually unavailable or hard to use.