| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Michelson.Typed.Util
Description
General-purpose utility functions for typed types.
Synopsis
- data DfsSettings x = DfsSettings {}
- data CtorEffectsApp x = CtorEffectsApp {}
- dfsInstr :: forall x inp out. Semigroup x => DfsSettings x -> (forall i o. Instr i o -> (Instr i o, x)) -> Instr inp out -> (Instr inp out, x)
- dfsFoldInstr :: forall x inp out. Semigroup x => DfsSettings x -> (forall i o. Instr i o -> x) -> Instr inp out -> x
- dfsModifyInstr :: DfsSettings () -> (forall i o. Instr i o -> Instr i o) -> Instr inp out -> Instr inp out
- linearizeLeft :: Instr inp out -> Instr inp out
- isStringValue :: Value t -> Maybe MText
- isBytesValue :: Value t -> Maybe ByteString
- allAtomicValues :: forall t a. (forall t'. Value t' -> Maybe a) -> Value t -> [a]
Documentation
data DfsSettings x Source #
Options for dfsInstr.
Constructors
| DfsSettings | |
Fields
| |
Instances
| Show (DfsSettings x) Source # | |
Defined in Michelson.Typed.Util Methods showsPrec :: Int -> DfsSettings x -> ShowS # show :: DfsSettings x -> String # showList :: [DfsSettings x] -> ShowS # | |
| Default (DfsSettings x) Source # | |
Defined in Michelson.Typed.Util Methods def :: DfsSettings x # | |
data CtorEffectsApp x Source #
Describes how intermediate nodes in instruction tree are accounted.
Constructors
| CtorEffectsApp | |
Fields
| |
Instances
| Show (CtorEffectsApp x) Source # | |
Defined in Michelson.Typed.Util Methods showsPrec :: Int -> CtorEffectsApp x -> ShowS # show :: CtorEffectsApp x -> String # showList :: [CtorEffectsApp x] -> ShowS # | |
dfsInstr :: forall x inp out. Semigroup x => DfsSettings x -> (forall i o. Instr i o -> (Instr i o, x)) -> Instr inp out -> (Instr inp out, x) Source #
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. Semigroup x => DfsSettings x -> (forall i o. Instr i o -> x) -> Instr inp out -> x Source #
Specialization of dfsInstr for case when changing the instruction is
not required.
dfsModifyInstr :: DfsSettings () -> (forall i o. Instr i o -> Instr i o) -> Instr inp out -> Instr inp out Source #
Specialization of dfsInstr which only modifies given instruction.
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
Instr have a single instruction (i. e. not Instr) in its second argument.
This function also erases redundant Nops.
Value analysis
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 an atomic value (i. e. that can not contain another value) can be converted to something. Recursively applies it to all atomic values in potentially non-atomic value. Collects extracted values in a list.
Perhaps one day we'll have dfsValue.