lorentz-0.12.1: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Run

Description

Lorentz contracts compilation.

Compilation in one scheme:

                    mkContract
                  mkContractWith
  ContractCode  -----------------→  Contract
 (Lorentz code)              (ready compiled contract)
        ↓                                ↑
        ↓                                ↑
defaultContractData            compileLorentzContract
   ContractData                          ↑
        ↓         ContractData           ↑
       (Lorentz code + compilation options)
Synopsis

Documentation

data Contract cp st Source #

Compiled Lorentz contract.

Constructors

(NiceParameterFull cp, NiceStorage st) => Contract 

Fields

  • cMichelsonContract :: Contract (ToT cp) (ToT st)

    Ready contract code.

  • cDocumentedCode :: ~(ContractCode cp st)

    Contract that contains documentation.

    We have to keep it separately, since optimizer is free to destroy documentation blocks. Also, it is not ContractDoc but Lorentz code because the latter is easier to modify.

Instances

Instances details
Eq (Contract cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

(==) :: Contract cp st -> Contract cp st -> Bool #

(/=) :: Contract cp st -> Contract cp st -> Bool #

Show (Contract cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> Contract cp st -> ShowS #

show :: Contract cp st -> String #

showList :: [Contract cp st] -> ShowS #

NFData (Contract cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

rnf :: Contract cp st -> () #

ContainsDoc (Contract cp st) Source # 
Instance details

Defined in Lorentz.Doc

ContainsUpdateableDoc (Contract cp st) Source # 
Instance details

Defined in Lorentz.Doc

Methods

modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> Contract cp st -> Contract cp st #

ToExpression (Contract cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

toExpression :: Contract cp st -> Expression

toMichelsonContract :: Contract cp st -> Contract (ToT cp) (ToT st) Source #

Demote Lorentz Contract to Michelson typed Contract.

defaultContract :: (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> Contract cp st Source #

Construct and compile Lorentz contract.

This is an alias for mkContract.

data CompilationOptions Source #

Options to control Lorentz to Michelson compilation.

Constructors

CompilationOptions 

Fields

defaultCompilationOptions :: CompilationOptions Source #

Runs Michelson optimizer with default config and does not touch strings and bytes.

intactCompilationOptions :: CompilationOptions Source #

Leave contract without any modifications. For testing purposes.

compileLorentz :: (inp :-> out) -> Instr (ToTs inp) (ToTs out) Source #

For use outside of Lorentz. Will use defaultCompilationOptions.

compileLorentzWithOptions :: CompilationOptions -> (inp :-> out) -> Instr (ToTs inp) (ToTs out) Source #

Compile Lorentz code, optionally running the optimizer, string and byte transformers.

mkContract :: (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> Contract cp st Source #

Construct and compile Lorentz contract.

Note that this accepts code with initial and final stacks unpaired for simplicity.

mkContractWith :: (NiceParameterFull cp, NiceStorage st) => CompilationOptions -> ContractCode cp st -> Contract cp st Source #

Version of mkContract that accepts custom compilation options.

data ContractData cp st Source #

Code for a contract along with compilation options for the Lorentz compiler.

It is expected that a Contract is one packaged entity, wholly controlled by its author. Therefore the author should be able to set all options that control contract's behavior.

This helps ensure that a given contract will be interpreted in the same way in all environments, like production and testing.

Raw ContractCode should not be used for distribution of contracts.

Constructors

(NiceParameterFull cp, NiceStorage st) => ContractData 

Fields

Instances

Instances details
ContainsDoc (ContractData cp st) Source # 
Instance details

Defined in Lorentz.Run

ContainsUpdateableDoc (ContractData cp st) Source # 
Instance details

Defined in Lorentz.Run

defaultContractData :: forall cp st. (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> ContractData cp st Source #

Compile contract with defaultCompilationOptions.

compileLorentzContract :: forall cp st. ContractData cp st -> Contract cp st Source #

Compile a whole contract to Michelson.

Note that compiled contract can be ill-typed in terms of Michelson code when some of the compilation options are used (e.g. when ccoDisableInitialCast is True, resulted contract can be ill-typed). However, compilation with defaultContractCompilationOptions should be valid.

cdCodeL :: forall cp st cp1 st1. (NiceParameterFull cp1, NiceStorage st1) => Lens (ContractData cp st) (ContractData cp1 st1) (ContractCode cp st) (ContractCode cp1 st1) Source #

interpretLorentzInstr :: (IsoValuesStack inp, IsoValuesStack out) => ContractEnv -> (inp :-> out) -> Rec Identity inp -> Either MichelsonFailed (Rec Identity out) Source #

Interpret a Lorentz instruction, for test purposes. Note that this does not run the optimizer.

interpretLorentzLambda :: (IsoValue inp, IsoValue out) => ContractEnv -> Lambda inp out -> inp -> Either MichelsonFailed out Source #

Like interpretLorentzInstr, but works on lambda rather than arbitrary instruction.

analyzeLorentz :: (inp :-> out) -> AnalyzerRes Source #

Lorentz version of analyzer.