Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains everything related to compilation from Indigo to Lorentz, including plain Indigo code, as well as Indigo contracts.
Synopsis
- compileIndigo :: forall n inp a. (SingI (ToPeano n), Default (MetaData inp), AreIndigoParams (ToPeano n) inp, KnownValue a) => IndigoWithParams (ToPeano n) inp a -> inp :-> inp
- type family IndigoWithParams n inp a where ...
- type IndigoContract param st = (HasStorage st, HasSideEffects) => Var param -> IndigoM ()
- compileIndigoContract :: forall param st. (KnownValue param, IsObject st) => IndigoContract param st -> ContractCode param st
- type Ops = [Operation]
- type HasSideEffects = Given (Var Ops)
- operationsVar :: HasSideEffects => Var Ops
- type HasStorage st = Given (Var st)
- storageVar :: HasStorage st => Var st
Documentation
compileIndigo :: forall n inp a. (SingI (ToPeano n), Default (MetaData inp), AreIndigoParams (ToPeano n) inp, KnownValue a) => IndigoWithParams (ToPeano n) inp a -> inp :-> inp Source #
Compile Indigo code to Lorentz.
Note: it is necessary to specify the number of parameters (using the first
type variable) of the Indigo function. Also, these should be on the top of
the input stack in inverse order (see IndigoWithParams
).
type family IndigoWithParams n inp a where ... Source #
Type of a function with n
Var
arguments and IndigoM a
result.
Note that the arguments are the first n
elements of the inp
stack in
inverse order, for example:
IndigoWithParams ('S ('S 'Z)) '[a, b, c] x
is the same as:
Var b -> Var a -> IndigoM x
IndigoWithParams 'Z _ a = IndigoM a | |
IndigoWithParams ('S n) inp a = Var (At n inp) -> IndigoWithParams n inp a |
type IndigoContract param st = (HasStorage st, HasSideEffects) => Var param -> IndigoM () Source #
Type of a contract that can be compiled to Lorentz with compileIndigoContract
.
compileIndigoContract :: forall param st. (KnownValue param, IsObject st) => IndigoContract param st -> ContractCode param st Source #
Compile Indigo code to Lorentz contract.
Drop elements from the stack to return only [Operation]
and storage
.
type HasSideEffects = Given (Var Ops) Source #
Allows to get a variable with operations
operationsVar :: HasSideEffects => Var Ops Source #
Return a variable which refers to a stack cell with operations
type HasStorage st = Given (Var st) Source #
Allows to get a variable with storage
storageVar :: HasStorage st => Var st Source #
Return a variable which refers to a stack cell with storage