Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data Contract cp st = (NiceParameterFull cp, NiceStorage st) => Contract {
- cMichelsonContract :: Contract (ToT cp) (ToT st)
- cDocumentedCode :: ~(ContractCode cp st)
- toMichelsonContract :: Contract cp st -> Contract (ToT cp) (ToT st)
- defaultContract :: (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> Contract cp st
- data CompilationOptions = CompilationOptions {
- coOptimizerConf :: Maybe OptimizerConf
- coStringTransformer :: (Bool, MText -> MText)
- coBytesTransformer :: (Bool, ByteString -> ByteString)
- coDisableInitialCast :: Bool
- defaultCompilationOptions :: CompilationOptions
- intactCompilationOptions :: CompilationOptions
- coBytesTransformerL :: Lens' CompilationOptions (Bool, ByteString -> ByteString)
- coOptimizerConfL :: Lens' CompilationOptions (Maybe OptimizerConf)
- coStringTransformerL :: Lens' CompilationOptions (Bool, MText -> MText)
- compileLorentz :: (inp :-> out) -> Instr (ToTs inp) (ToTs out)
- compileLorentzWithOptions :: CompilationOptions -> (inp :-> out) -> Instr (ToTs inp) (ToTs out)
- mkContract :: (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> Contract cp st
- mkContractWith :: (NiceParameterFull cp, NiceStorage st) => CompilationOptions -> ContractCode cp st -> Contract cp st
- data ContractData cp st = (NiceParameterFull cp, NiceStorage st) => ContractData {
- cdCode :: ContractCode cp st
- cdCompilationOptions :: CompilationOptions
- defaultContractData :: forall cp st. (NiceParameterFull cp, NiceStorage st) => ContractCode cp st -> ContractData cp st
- compileLorentzContract :: forall cp st. ContractData cp st -> Contract cp st
- cdCodeL :: forall cp st cp1 st1. (NiceParameterFull cp1, NiceStorage st1) => Lens (ContractData cp st) (ContractData cp1 st1) (ContractCode cp st) (ContractCode cp1 st1)
- coDisableInitialCastL :: Lens' CompilationOptions Bool
- cdCompilationOptionsL :: forall cp st. Lens' (ContractData cp st) CompilationOptions
- interpretLorentzInstr :: (IsoValuesStack inp, IsoValuesStack out) => ContractEnv -> (inp :-> out) -> Rec Identity inp -> Either MichelsonFailureWithStack (Rec Identity out)
- interpretLorentzLambda :: (IsoValue inp, IsoValue out) => ContractEnv -> Lambda inp out -> inp -> Either MichelsonFailureWithStack out
- analyzeLorentz :: (inp :-> out) -> AnalyzerRes
Documentation
Compiled Lorentz contract.
Constructors
(NiceParameterFull cp, NiceStorage st) => Contract | |
Fields
|
Instances
Eq (Contract cp st) Source # | |
Show (Contract cp st) Source # | |
NFData (Contract cp st) Source # | |
Defined in Lorentz.Base | |
ContainsDoc (Contract cp st) Source # | |
Defined in Lorentz.Doc Methods buildDocUnfinalized :: Contract cp st -> ContractDoc # | |
ContainsUpdateableDoc (Contract cp st) Source # | |
Defined in Lorentz.Doc Methods modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> Contract cp st -> Contract cp st # | |
ToExpression (Contract cp st) Source # | |
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.
coOptimizerConfL :: Lens' CompilationOptions (Maybe OptimizerConf) Source #
coStringTransformerL :: Lens' CompilationOptions (Bool, MText -> MText) Source #
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
ContainsDoc (ContractData cp st) Source # | |
Defined in Lorentz.Run Methods buildDocUnfinalized :: ContractData cp st -> ContractDoc # | |
ContainsUpdateableDoc (ContractData cp st) Source # | |
Defined in Lorentz.Run Methods modifyDocEntirely :: (SomeDocItem -> SomeDocItem) -> ContractData cp st -> ContractData cp st # |
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 coDisableInitialCast
is True
, resulted contract can be ill-typed).
However, compilation with defaultCompilationOptions
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 #
cdCompilationOptionsL :: forall cp st. Lens' (ContractData cp st) CompilationOptions Source #
interpretLorentzInstr :: (IsoValuesStack inp, IsoValuesStack out) => ContractEnv -> (inp :-> out) -> Rec Identity inp -> Either MichelsonFailureWithStack (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 MichelsonFailureWithStack out Source #
Like interpretLorentzInstr
, but works on lambda rather than
arbitrary instruction.
analyzeLorentz :: (inp :-> out) -> AnalyzerRes Source #
Lorentz version of analyzer.