morley-1.16.1: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Morley.Michelson.Typed.Util

Description

General-purpose utility functions for typed types.

Synopsis

Documentation

data DfsSettings x Source #

Options for dfsInstr.

Constructors

DfsSettings 

Fields

Instances

Instances details
Show (DfsSettings x) Source # 
Instance details

Defined in Morley.Michelson.Typed.Util

Default (DfsSettings x) Source # 
Instance details

Defined in Morley.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

Instances details
Show (CtorEffectsApp x) Source # 
Instance details

Defined in Morley.Michelson.Typed.Util

ceaBottomToTop :: CtorEffectsApp x Source #

Gather effects first for children nodes, then for their parents.

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 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.

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 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 big_maps. E.g. A 'Right ()' value of type 'Either (BigMap k v) ()'.

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 heavy) contain one or more big_maps or tickets. The instruction can take the non-pushable 'Value heavy' and reconstruct the original 'Value st' without using any EMPTY_BIG_MAP.

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.