Morley Lorentz EDSL
Table of contents
Overview
Lorentz is a powerful meta-programming tool which allows one to write Michelson contracts directly in Haskell.
Haskell's type checker and automatic type inference facilitate contracts implementation and reduce boilerplate related to types.
Adoption of Algebraic Data Types makes work with complex objects safe and convenient.
Later Lorentz contract can be dumped as a plain textual Michelson contract using functions from Michelson.Printer
.
As an addition, you can optimize the transpiled Michelson contract before printing
using functions from Michelson.Optimizer
.
E.g. this optimizer will replace IF {} {}
with DROP
. For more possible optimizations
please refer to the module mentioned earlier.
You can find Lorentz instructions in Lorentz
modules.
Examples of using Lorentz eDSL reside in the morley-ledgers
or tezos-btc
repos.
For more information, refer to that README's in the corresponding repositories.
Also, to get more information about Lorentz you can read our blogpost.
Writing contracts in Lorentz
Basically, Lorentz function is just the haskell function that transforms one
stack to another, this can be presented as the following operator:
(inp :: [Type]) :-> (out :: [Type])
In order to list types on the stack, we will use :
operator.
For example, Natural : Integer : Bool : '[]
.
Such design provides a nice code decomposition ability.
Contract code in Lorentz is Lorentz function with specific type:
type ContractOut storage = '[([Operation], storage)]
type ContractCode parameter storage = '[(parameter, storage)] :-> ContractOut storage
Lorentz reimplements all existing instructions and
macros from Michelson.
Apart from reimplementing existing Michelson functionality, Lorentz provides bunch of
additional features:
- Pattern-matching on ADTs.
data TrafficLight
= Red
| Yellow
| Green
deriving stock Generic
deriving anyclass IsoValue
showTrafficLight :: TrafficLight : s :-> MText : s
showTrafficLight = caseT
( #cRed /-> push [mt|Red|]
, #cYellow /-> push [mt|Yellow|]
, #cGreen /-> push [mt|Green|]
)
RebindableSyntax
for Lorentz instructions, including do
notation and if
operator
sumIsGt10 :: Integer : Integer : s :-> Bool : s
sumIsGt10 = do
add
dip $ push @Integer 10
gt
foo :: Integer : s :-> Integer : s
foo = do
dup
sumIsGt10
if Holds
then do push @Integer 1
else do push @Integer -1
data UserInfo = UserInfo
{ firstName :: MText
, secondName :: MText
, userId :: Natural
} deriving stock Generic
deriving anyclass IsoValue
getFullName :: UserInfo : s :-> MText : s
getFullName = do
getField #firstName
dip $ toField #secondName
concat
-
Automatic contracts documentation generation.
Lorentz provides primitives for embedding documentation in the contract code and
functions to produce documentation in Markdown, they can be found in
Lorentz.Doc
and Michelson.Doc
modules.
Documentation examples can be found here.
Sample smart contract written in Lorentz
Example contract with autodoc and custom data-type tree:
data MeasurementMethod
= ParrotStep
| MonkeyStep
| ElephantStep
$(customGeneric "MeasurementMethod" rightBalanced)
deriving anyclass instance IsoValue MeasurementMethod
deriving anyclass instance HasAnnotation MeasurementMethod
instance TypeHasDoc MeasurementMethod where
typeDocName _ = "MeasurementMethod"
typeDocMdDescription =
"This type defines the way of measuring boa length. \
\Single boa constrictor corresponds to 38 parrot steps, 31 monkey step \
\and 9 elephant steps."
data Parameter
= MeasureBoaConstrictor ("method" :! MeasurementMethod)
| Zero ()
deriving stock Generic
deriving anyclass IsoValue
instance ParameterHasEntrypoints Parameter where
type ParameterEntrypointsDerivation Parameter = EpdPlain
type Storage = Natural
measureBoaConstrictor :: ContractCode Parameter Storage
measureBoaConstrictor = docGroup (DName "Boa constrictor measurement") $ do
doc $ DDescription "This contract measures boa constrictor."
unpair
dip drop
entryCase @Parameter (Proxy @PlainEntrypointsKind)
( #cMeasureBoaConstrictor /-> do
doc $ DDescription "Measure the boa constrictor with given method."
fromNamed #method
caseT @MeasurementMethod
( #cParrotStep /-> push @Natural 38
, #cMonkeyStep /-> push @Natural 31
, #cElephantStep /-> push @Natural 9
)
, #cZero /-> do
doc $ DDescription "Put zero to the storage."
drop; push @Natural 0
)
nil; pair
Generated documentation
Generated documentation for this contract can be found here.
Transpiled Michelson contract
parameter (or (or :method %measureBoaConstrictor unit
(or unit
unit))
(unit %zero));
storage nat;
code { CAST (pair (or (or unit (or unit unit)) unit) nat);
DUP;
CAR;
DIP { CDR };
DIP { DROP };
IF_LEFT { IF_LEFT { DROP;
PUSH nat 38 }
{ IF_LEFT { DROP;
PUSH nat 31 }
{ DROP;
PUSH nat 9 } } }
{ DROP;
PUSH nat 0 };
NIL operation;
PAIR };
FAQ
-
Q: I added a new parameter case to contract and GHC went mad.
A: Ensure that your number of entry points does not exceed the limit set in Util.TypeTuple.Instances
.
-
Q: I added one more datatype that is used in the contract and GHC reports with errors related
to Rep
type family.
A: Make sure your datatype derives Generic
instance and all primitive types used in it have IsPrimitiveValue
set to True
.