morley-1.20.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Optimizer.Utils

Description

Utilities for writing optimizer rules.

Synopsis

Documentation

pattern (:#) :: Instr inp b -> Instr b out -> Instr inp out infixr 8 Source #

This is a redefinition of (:#) from Morley.Michelson.Typed.Instr that is particularly useful for writing optimizer rules. When matching on an instruction x that isn't Seq, it behaves as if it matched on x :# Nop.

When constructing instructions using this pattern, Nop is automatically removed.

To understand why this is useful, consider that a given instruction sequence can appear in the middle of a sequence, and then a :# b :# tail will match, or at the end of the sequence, and then a :# b will match. Thus, to cover all cases one would have to duplicate most rules.

This definition of (:#) makes it so we can always assume there's a tail. However, we don't need it when matching on single instructions.

Thus, the rule of thumb is this: if you're matching on a single instruction, everything is fine. If you're matching on a sequence, i.e. using (:#), then always match on tail, e.g.

dupSwap2dup :: Rule
dupSwap2dup = Rule $ case
  DUP :# SWAP :# c -> Just $ DUP :# c
  _                -> Nothing

But this works, too:

ifNopNop2Drop :: Rule
ifNopNop2Drop = Rule $ case
  IF Nop Nop -> Just DROP
  _          -> Nothing

orRule :: (Rule -> Rule) -> (Rule -> Rule) -> Rule -> Rule Source #

Combine two rule fixpoints.

orSimpleRule :: (Rule -> Rule) -> Rule -> Rule -> Rule Source #

Combine a rule fixpoint and a simple rule.

fixpoint :: (Rule -> Rule) -> Rule Source #

Turn rule fixpoint into rule.

applyOnce :: Rule -> Instr inp out -> (Any Bool, Instr inp out) Source #

Apply the rule once, if it fails, return the instruction unmodified.

Also returns a flag showing whether the rule succeeded or not.

whileApplies :: Rule -> Rule Source #

Apply a rule to the same code, until it fails.

linearizeAndReapply :: Rule -> Instr inp out -> Instr inp out Source #

Append LHS of Seq to RHS and re-run pointwise ocRuleset at each point. That might cause reinvocation of this function (see defaultRule'), but effectively this ensures it will flatten any Seq-tree right-to-left, while evaling no more than once on each node.

The reason this function invokes ocRuleset is when you append an instr to already-optimised RHS of Seq, you might get an optimisable tree.

The argument is a local, non-structurally-recursive ocRuleset.