morley-0.7.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Typed.Util

Contents

Description

General-purpose utility functions for typed types.

Synopsis

Documentation

data DfsSettings x Source #

Options for dfsInstr.

Constructors

DfsSettings 

Fields

Instances
Show (DfsSettings x) Source # 
Instance details

Defined in Michelson.Typed.Util

Default (DfsSettings x) Source # 
Instance details

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

  • ceaName :: Text

    Name of this way.

  • ceaApplyEffects :: forall i o. Semigroup x => x -> x -> Instr i o -> (Instr i o, x)

    This function accepts: 1. Effects gathered after applying step to node's children, but before applying it to the node itself. 2. Effects gathered after applying step to the given intermediate node. 3. Instruction resulting after all modifications produced by step.

Instances
Show (CtorEffectsApp x) Source # 
Instance details

Defined in Michelson.Typed.Util

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

isStringValue :: Value t -> Maybe MText Source #

If value is a string, return the stored string.

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.