Safe Haskell | None |
---|---|
Language | Haskell2010 |
Duplication of Backend functions, but without input and output stack.
Synopsis
- new :: IsExpr ex x => ex -> IndigoM (Var x)
- setVar :: IsExpr ex x => Var x -> ex -> IndigoM ()
- setField :: (ex :~> ftype, IsObject dt, IsObject ftype, HasField dt fname ftype) => Var dt -> Label fname -> ex -> IndigoM ()
- (+=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Add n m, ArithResHs Add n m ~ m) => Var m -> ex1 -> IndigoM ()
- (-=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Sub n m, ArithResHs Sub n m ~ m) => Var m -> ex1 -> IndigoM ()
- (*=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Mul n m, ArithResHs Mul n m ~ m) => Var m -> ex1 -> IndigoM ()
- (<<<=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Lsl n m, ArithResHs Lsl n m ~ m) => Var m -> ex1 -> IndigoM ()
- (>>>=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Lsr n m, ArithResHs Lsr n m ~ m) => Var m -> ex1 -> IndigoM ()
- (&&=) :: (IsExpr ex1 n, IsObject m, ArithOpHs And n m, ArithResHs And n m ~ m) => Var m -> ex1 -> IndigoM ()
- (||=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Or n m, ArithResHs Or n m ~ m) => Var m -> ex1 -> IndigoM ()
- (^=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Xor n m, ArithResHs Xor n m ~ m) => Var m -> ex1 -> IndigoM ()
- (=:) :: IsExpr ex x => Var x -> ex -> IndigoM ()
- getStorageField :: forall store ftype fname. (HasStorage store, HasField store fname ftype) => Label fname -> IndigoM (Var ftype)
- setStorageField :: forall store name ftype ex. (HasStorage store, ex :~> ftype, IsObject store, IsObject ftype, HasField store name ftype) => Label name -> ex -> IndigoM ()
- updateStorageField :: forall store ftype fname fex. (HasStorage store, fex :~> ftype, HasField store fname ftype, IsObject store, IsObject ftype) => Label fname -> (Var ftype -> IndigoM fex) -> IndigoM ()
- if_ :: forall a b ex. (IfConstraint a b, ex :~> Bool) => ex -> IndigoM a -> IndigoM b -> IndigoM (RetVars a)
- when :: exc :~> Bool => exc -> IndigoM () -> IndigoM ()
- unless :: exc :~> Bool => exc -> IndigoM () -> IndigoM ()
- ifSome :: forall x a b ex. (KnownValue x, ex :~> Maybe x, IfConstraint a b) => ex -> (Var x -> IndigoM a) -> IndigoM b -> IndigoM (RetVars a)
- ifNone :: forall x a b ex. (KnownValue x, ex :~> Maybe x, IfConstraint a b) => ex -> IndigoM b -> (Var x -> IndigoM a) -> IndigoM (RetVars a)
- whenSome :: forall x exa. (KnownValue x, exa :~> Maybe x) => exa -> (Var x -> IndigoM ()) -> IndigoM ()
- whenNone :: forall x exa. (KnownValue x, exa :~> Maybe x) => exa -> IndigoM () -> IndigoM ()
- ifRight :: forall x y a b ex. (KnownValue x, KnownValue y, ex :~> Either y x, IfConstraint a b) => ex -> (Var x -> IndigoM a) -> (Var y -> IndigoM b) -> IndigoM (RetVars a)
- ifLeft :: forall x y a b ex. (KnownValue x, KnownValue y, ex :~> Either y x, IfConstraint a b) => ex -> (Var y -> IndigoM b) -> (Var x -> IndigoM a) -> IndigoM (RetVars a)
- whenRight :: forall x y ex. (KnownValue x, KnownValue y, ex :~> Either y x) => ex -> (Var x -> IndigoM ()) -> IndigoM ()
- whenLeft :: forall x y ex. (KnownValue x, KnownValue y, ex :~> Either y x) => ex -> (Var y -> IndigoM ()) -> IndigoM ()
- ifCons :: forall x a b ex. (KnownValue x, ex :~> List x, IfConstraint a b) => ex -> (Var x -> Var (List x) -> IndigoM a) -> IndigoM b -> IndigoM (RetVars a)
- case_ :: forall dt guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, RecFromTuple clauses, guard :~> dt) => guard -> IsoRecTuple clauses -> IndigoM (RetVars ret)
- caseRec :: forall dt guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, guard :~> dt) => guard -> clauses -> IndigoM (RetVars ret)
- entryCase :: forall dt entrypointKind guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, RecFromTuple clauses, DocumentEntrypoints entrypointKind dt, guard :~> dt) => Proxy entrypointKind -> guard -> IsoRecTuple clauses -> IndigoM (RetVars ret)
- entryCaseRec :: forall dt entrypointKind guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, DocumentEntrypoints entrypointKind dt, guard :~> dt) => Proxy entrypointKind -> guard -> clauses -> IndigoM (RetVars ret)
- entryCaseSimple :: forall cp guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) cp ret clauses, RecFromTuple clauses, DocumentEntrypoints PlainEntrypointsKind cp, NiceParameterFull cp, RequireFlatParamEps cp, guard :~> cp) => guard -> IsoRecTuple clauses -> IndigoM (RetVars ret)
- (//->) :: (CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))), ScopeCodeGen retBr, ret ~ RetExprs retBr, RetOutStack ret ~ RetOutStack retBr, KnownValue x, name ~ AppendSymbol "c" ctor) => Label name -> (Var x -> IndigoM retBr) -> IndigoMCaseClauseL IndigoM ret ('CaseClauseParam ctor ('OneField x))
- (#=) :: (CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))), ScopeCodeGen retBr, ret ~ RetExprs retBr, RetOutStack ret ~ RetOutStack retBr, KnownValue x, name ~ AppendSymbol "c" ctor) => Label name -> (Var x -> IndigoM retBr) -> IndigoMCaseClauseL IndigoM ret ('CaseClauseParam ctor ('OneField x))
- scope :: forall a. ScopeCodeGen a => IndigoM a -> IndigoFunction a
- defFunction :: forall a. ScopeCodeGen a => IndigoM a -> IndigoFunction a
- defContract :: (HasSideEffects => IndigoM ()) -> HasSideEffects => IndigoProcedure
- defNamedPureLambda1 :: forall argExpr res. (ToExpr argExpr, Typeable res, ExecuteLambdaPure1C (ExprType argExpr) res, CreateLambdaPure1C (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> argExpr -> IndigoM (RetVars res)
- defNamedLambda1 :: forall st argExpr res. (ToExpr argExpr, Typeable res, ExecuteLambda1C st (ExprType argExpr) res, CreateLambda1C st (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> argExpr -> IndigoM (RetVars res)
- defNamedLambda0 :: forall st res. (Typeable res, ExecuteLambda1C st () res, CreateLambda1C st () res) => String -> IndigoM res -> IndigoM (RetVars res)
- defNamedEffLambda1 :: forall st argExpr res. (ToExpr argExpr, Typeable res, ExecuteLambdaEff1C st (ExprType argExpr) res, CreateLambdaEff1C st (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> argExpr -> IndigoM (RetVars res)
- while :: forall ex. ex :~> Bool => ex -> IndigoM () -> IndigoM ()
- whileLeft :: forall x y ex. (ex :~> Either y x, KnownValue y, KnownValue x) => ex -> (Var y -> IndigoM ()) -> IndigoM (Var x)
- forEach :: forall a e. (IterOpHs a, KnownValue (IterOpElHs a), e :~> a) => e -> (Var (IterOpElHs a) -> IndigoM ()) -> IndigoM ()
- selfCalling :: forall p mname. (NiceParameterFull p, KnownValue (GetEntrypointArgCustom p mname)) => EntrypointRef mname -> IndigoM (Var (ContractRef (GetEntrypointArgCustom p mname)))
- contractCalling :: forall cp epRef epArg addr exAddr. (HasEntrypointArg cp epRef epArg, ToTAddress cp addr, ToT addr ~ ToT Address, exAddr :~> addr, KnownValue epArg) => epRef -> exAddr -> IndigoM (Var (Maybe (ContractRef epArg)))
- doc :: DocItem di => di -> IndigoM ()
- docGroup :: DocGrouping -> IndigoM () -> IndigoM ()
- docStorage :: forall storage. TypeHasDoc storage => IndigoM ()
- contractName :: Text -> IndigoM () -> IndigoM ()
- contractGeneral :: IndigoM () -> IndigoM ()
- contractGeneralDefault :: IndigoM ()
- finalizeParamCallingDoc :: forall param x. (ToExpr param, NiceParameterFull (ExprType param), RequireSumType (ExprType param), HasCallStack) => (Var (ExprType param) -> IndigoM x) -> param -> IndigoM x
- anchor :: Text -> IndigoM ()
- description :: Markdown -> IndigoM ()
- example :: forall a. NiceParameter a => a -> IndigoM ()
- transferTokens :: (IsExpr exp p, IsExpr exm Mutez, IsExpr exc (ContractRef p), NiceParameter p, HasSideEffects) => exp -> exm -> exc -> IndigoM ()
- setDelegate :: (HasSideEffects, IsExpr ex (Maybe KeyHash)) => ex -> IndigoM ()
- createContract :: (IsObject st, IsExpr exk (Maybe KeyHash), IsExpr exm Mutez, IsExpr exs st, NiceStorage st, NiceParameterFull param, HasSideEffects) => (HasStorage st => Var param -> IndigoM ()) -> exk -> exm -> exs -> IndigoM (Var Address)
- createLorentzContract :: (IsObject st, IsExpr exk (Maybe KeyHash), IsExpr exm Mutez, IsExpr exs st, NiceStorage st, NiceParameterFull param, HasSideEffects) => Contract param st -> exk -> exm -> exs -> IndigoM (Var Address)
- failWith :: forall r a ex. IsExpr ex a => ex -> IndigoM r
- assert :: forall x ex. (IsError x, IsExpr ex Bool) => x -> ex -> IndigoM ()
- failCustom :: forall r tag err ex. (err ~ ErrorArg tag, CustomErrorHasDoc tag, NiceConstant err, ex :~> err) => Label tag -> ex -> IndigoM r
- failCustom_ :: forall r tag notVoidErrorMsg. (RequireNoArgError tag notVoidErrorMsg, CustomErrorHasDoc tag) => Label tag -> IndigoM r
- failUnexpected_ :: MText -> IndigoM r
- assertCustom :: forall tag err errEx ex. (err ~ ErrorArg tag, CustomErrorHasDoc tag, NiceConstant err, IsExpr errEx err, IsExpr ex Bool) => Label tag -> errEx -> ex -> IndigoM ()
- assertCustom_ :: forall tag notVoidErrorMsg ex. (RequireNoArgError tag notVoidErrorMsg, CustomErrorHasDoc tag, IsExpr ex Bool) => Label tag -> ex -> IndigoM ()
- comment :: CommentType -> IndigoM ()
- justComment :: Text -> IndigoM ()
- commentAroundFun :: Text -> IndigoM a -> IndigoM a
- commentAroundStmt :: Text -> IndigoM a -> IndigoM a
- type IndigoFunction ret = IndigoM (RetVars ret)
- type IndigoProcedure = IndigoM ()
- type IndigoEntrypoint param = param -> IndigoProcedure
- liftIndigoState :: (forall inp. SomeIndigoState inp a) -> IndigoM a
Assignment and modifications
new :: IsExpr ex x => ex -> IndigoM (Var x) Source #
Create a new variable with the result of the given expression as its initial value.
setVar :: IsExpr ex x => Var x -> ex -> IndigoM () Source #
Set the given variable to the result of the given expression.
setField :: (ex :~> ftype, IsObject dt, IsObject ftype, HasField dt fname ftype) => Var dt -> Label fname -> ex -> IndigoM () Source #
(+=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Add n m, ArithResHs Add n m ~ m) => Var m -> ex1 -> IndigoM () Source #
(-=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Sub n m, ArithResHs Sub n m ~ m) => Var m -> ex1 -> IndigoM () Source #
(*=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Mul n m, ArithResHs Mul n m ~ m) => Var m -> ex1 -> IndigoM () Source #
(<<<=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Lsl n m, ArithResHs Lsl n m ~ m) => Var m -> ex1 -> IndigoM () Source #
(>>>=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Lsr n m, ArithResHs Lsr n m ~ m) => Var m -> ex1 -> IndigoM () Source #
(&&=) :: (IsExpr ex1 n, IsObject m, ArithOpHs And n m, ArithResHs And n m ~ m) => Var m -> ex1 -> IndigoM () Source #
(||=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Or n m, ArithResHs Or n m ~ m) => Var m -> ex1 -> IndigoM () Source #
(^=) :: (IsExpr ex1 n, IsObject m, ArithOpHs Xor n m, ArithResHs Xor n m ~ m) => Var m -> ex1 -> IndigoM () Source #
Storage Fields
getStorageField :: forall store ftype fname. (HasStorage store, HasField store fname ftype) => Label fname -> IndigoM (Var ftype) Source #
Get a field from the storage, returns a variable.
Note that the storage type almost always needs to be specified.
setStorageField :: forall store name ftype ex. (HasStorage store, ex :~> ftype, IsObject store, IsObject ftype, HasField store name ftype) => Label name -> ex -> IndigoM () Source #
Sets a storage field to a new value.
updateStorageField :: forall store ftype fname fex. (HasStorage store, fex :~> ftype, HasField store fname ftype, IsObject store, IsObject ftype) => Label fname -> (Var ftype -> IndigoM fex) -> IndigoM () Source #
Updates a storage field by using an updating IndigoM
.
Conditional
if_ :: forall a b ex. (IfConstraint a b, ex :~> Bool) => ex -> IndigoM a -> IndigoM b -> IndigoM (RetVars a) Source #
when :: exc :~> Bool => exc -> IndigoM () -> IndigoM () Source #
Run the instruction when the condition is met, do nothing otherwise.
ifSome :: forall x a b ex. (KnownValue x, ex :~> Maybe x, IfConstraint a b) => ex -> (Var x -> IndigoM a) -> IndigoM b -> IndigoM (RetVars a) Source #
ifNone :: forall x a b ex. (KnownValue x, ex :~> Maybe x, IfConstraint a b) => ex -> IndigoM b -> (Var x -> IndigoM a) -> IndigoM (RetVars a) Source #
whenSome :: forall x exa. (KnownValue x, exa :~> Maybe x) => exa -> (Var x -> IndigoM ()) -> IndigoM () Source #
Run the instruction when the given expression returns Just
a value,
do nothing otherwise.
whenNone :: forall x exa. (KnownValue x, exa :~> Maybe x) => exa -> IndigoM () -> IndigoM () Source #
Run the instruction when the given expression returns Nothing
,
do nothing otherwise.
ifRight :: forall x y a b ex. (KnownValue x, KnownValue y, ex :~> Either y x, IfConstraint a b) => ex -> (Var x -> IndigoM a) -> (Var y -> IndigoM b) -> IndigoM (RetVars a) Source #
ifLeft :: forall x y a b ex. (KnownValue x, KnownValue y, ex :~> Either y x, IfConstraint a b) => ex -> (Var y -> IndigoM b) -> (Var x -> IndigoM a) -> IndigoM (RetVars a) Source #
whenRight :: forall x y ex. (KnownValue x, KnownValue y, ex :~> Either y x) => ex -> (Var x -> IndigoM ()) -> IndigoM () Source #
whenLeft :: forall x y ex. (KnownValue x, KnownValue y, ex :~> Either y x) => ex -> (Var y -> IndigoM ()) -> IndigoM () Source #
ifCons :: forall x a b ex. (KnownValue x, ex :~> List x, IfConstraint a b) => ex -> (Var x -> Var (List x) -> IndigoM a) -> IndigoM b -> IndigoM (RetVars a) Source #
Case
case_ :: forall dt guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, RecFromTuple clauses, guard :~> dt) => guard -> IsoRecTuple clauses -> IndigoM (RetVars ret) Source #
caseRec
for tuples.
caseRec :: forall dt guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, guard :~> dt) => guard -> clauses -> IndigoM (RetVars ret) Source #
A case statement for indigo. See examples for a sample usage.
entryCase :: forall dt entrypointKind guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, RecFromTuple clauses, DocumentEntrypoints entrypointKind dt, guard :~> dt) => Proxy entrypointKind -> guard -> IsoRecTuple clauses -> IndigoM (RetVars ret) Source #
entryCaseRec
for tuples.
entryCaseRec :: forall dt entrypointKind guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) dt ret clauses, DocumentEntrypoints entrypointKind dt, guard :~> dt) => Proxy entrypointKind -> guard -> clauses -> IndigoM (RetVars ret) Source #
caseRec
for pattern-matching on parameter.
entryCaseSimple :: forall cp guard ret clauses. (CaseCommonF (IndigoMCaseClauseL IndigoM) cp ret clauses, RecFromTuple clauses, DocumentEntrypoints PlainEntrypointsKind cp, NiceParameterFull cp, RequireFlatParamEps cp, guard :~> cp) => guard -> IsoRecTuple clauses -> IndigoM (RetVars ret) Source #
(//->) :: (CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))), ScopeCodeGen retBr, ret ~ RetExprs retBr, RetOutStack ret ~ RetOutStack retBr, KnownValue x, name ~ AppendSymbol "c" ctor) => Label name -> (Var x -> IndigoM retBr) -> IndigoMCaseClauseL IndigoM ret ('CaseClauseParam ctor ('OneField x)) infixr 0 Source #
(#=) :: (CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))), ScopeCodeGen retBr, ret ~ RetExprs retBr, RetOutStack ret ~ RetOutStack retBr, KnownValue x, name ~ AppendSymbol "c" ctor) => Label name -> (Var x -> IndigoM retBr) -> IndigoMCaseClauseL IndigoM ret ('CaseClauseParam ctor ('OneField x)) infixr 0 Source #
Use this instead of /->
.
This operator is like /->
but wraps a body into IndigoAnyOut
,
which is needed for two reasons: to allow having any output stack
and to allow returning not exactly the same values.
It has the added benefit of not being an arrow, so in case the body of the clause is a lambda there won't be several.
Scope
scope :: forall a. ScopeCodeGen a => IndigoM a -> IndigoFunction a Source #
defFunction :: forall a. ScopeCodeGen a => IndigoM a -> IndigoFunction a Source #
Alias for scope
we use in the tutorial.
defContract :: (HasSideEffects => IndigoM ()) -> HasSideEffects => IndigoProcedure Source #
A more specific version of defFunction
meant to more easily create
IndigoContract
s.
Used in the tutorial. The HasSideEffects
constraint is
specified to avoid the warning for redundant constraints.
defNamedPureLambda1 :: forall argExpr res. (ToExpr argExpr, Typeable res, ExecuteLambdaPure1C (ExprType argExpr) res, CreateLambdaPure1C (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> argExpr -> IndigoM (RetVars res) Source #
Like defNamedEffLambda1 but doesn't modify storage and doesn't make side effects.
defNamedLambda1 :: forall st argExpr res. (ToExpr argExpr, Typeable res, ExecuteLambda1C st (ExprType argExpr) res, CreateLambda1C st (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> argExpr -> IndigoM (RetVars res) Source #
Like defNamedEffLambda1 but doesn't make side effects.
defNamedLambda0 :: forall st res. (Typeable res, ExecuteLambda1C st () res, CreateLambda1C st () res) => String -> IndigoM res -> IndigoM (RetVars res) Source #
Like defNamedLambda1 but doesn't take an argument.
defNamedEffLambda1 :: forall st argExpr res. (ToExpr argExpr, Typeable res, ExecuteLambdaEff1C st (ExprType argExpr) res, CreateLambdaEff1C st (ExprType argExpr) res) => String -> (Var (ExprType argExpr) -> IndigoM res) -> argExpr -> IndigoM (RetVars res) Source #
Family of defNamed*LambdaN
functions put an Indigo computation
on the stack to later call it avoiding code duplication.
defNamed*LambdaN
takes a computation with N arguments.
This family of functions add some overhead to contract byte size
for every call of the function,
therefore, DON'T use defNamed*LambdaN
if:
* Your computation is pretty small.
It would be cheaper just to inline it, so use defFunction
.
* Your computation is called only once, in this case also use defFunction
.
Also, pay attention that defNamed*LambdaN
accepts a string that is
a name of the passed computation. Be careful and make sure that all
declared computations have different names.
Later the name will be removed.
Pay attention, that lambda argument will be evaluated to variable before lambda calling.
TODO Approach with lambda names has critical pitfall:
in case if a function takes Label name
, lambda body
won't be regenerated for every different label.
So be carefully, this will be fixed in a following issue.
Loop
whileLeft :: forall x y ex. (ex :~> Either y x, KnownValue y, KnownValue x) => ex -> (Var y -> IndigoM ()) -> IndigoM (Var x) Source #
forEach :: forall a e. (IterOpHs a, KnownValue (IterOpElHs a), e :~> a) => e -> (Var (IterOpElHs a) -> IndigoM ()) -> IndigoM () Source #
For statements to iterate over a container.
Contract call
selfCalling :: forall p mname. (NiceParameterFull p, KnownValue (GetEntrypointArgCustom p mname)) => EntrypointRef mname -> IndigoM (Var (ContractRef (GetEntrypointArgCustom p mname))) Source #
contractCalling :: forall cp epRef epArg addr exAddr. (HasEntrypointArg cp epRef epArg, ToTAddress cp addr, ToT addr ~ ToT Address, exAddr :~> addr, KnownValue epArg) => epRef -> exAddr -> IndigoM (Var (Maybe (ContractRef epArg))) Source #
Documentation
docGroup :: DocGrouping -> IndigoM () -> IndigoM () Source #
Group documentation built in the given piece of code into a block dedicated to one thing, e.g. to one entrypoint.
docStorage :: forall storage. TypeHasDoc storage => IndigoM () Source #
Insert documentation of the contract's storage type. The type should be passed using type applications.
contractName :: Text -> IndigoM () -> IndigoM () Source #
Give a name to the given contract. Apply it to the whole contract code.
contractGeneral :: IndigoM () -> IndigoM () Source #
Attach general info to the given contract.
contractGeneralDefault :: IndigoM () Source #
Attach default general info to the contract documentation.
finalizeParamCallingDoc :: forall param x. (ToExpr param, NiceParameterFull (ExprType param), RequireSumType (ExprType param), HasCallStack) => (Var (ExprType param) -> IndigoM x) -> param -> IndigoM x Source #
Indigo version for the homonym Lorentz function.
Short-handed doc item
description :: Markdown -> IndigoM () Source #
Put a DDescription
doc item.
example :: forall a. NiceParameter a => a -> IndigoM () Source #
Put a DEntrypointExample
doc item.
Side-effects operations
transferTokens :: (IsExpr exp p, IsExpr exm Mutez, IsExpr exc (ContractRef p), NiceParameter p, HasSideEffects) => exp -> exm -> exc -> IndigoM () Source #
setDelegate :: (HasSideEffects, IsExpr ex (Maybe KeyHash)) => ex -> IndigoM () Source #
createContract :: (IsObject st, IsExpr exk (Maybe KeyHash), IsExpr exm Mutez, IsExpr exs st, NiceStorage st, NiceParameterFull param, HasSideEffects) => (HasStorage st => Var param -> IndigoM ()) -> exk -> exm -> exs -> IndigoM (Var Address) Source #
Create contract using default compilation options for Lorentz compiler.
See Lorentz.Run.
createLorentzContract :: (IsObject st, IsExpr exk (Maybe KeyHash), IsExpr exm Mutez, IsExpr exs st, NiceStorage st, NiceParameterFull param, HasSideEffects) => Contract param st -> exk -> exm -> exs -> IndigoM (Var Address) Source #
Create contract from raw Lorentz Contract
.
Failures
failCustom :: forall r tag err ex. (err ~ ErrorArg tag, CustomErrorHasDoc tag, NiceConstant err, ex :~> err) => Label tag -> ex -> IndigoM r Source #
failCustom_ :: forall r tag notVoidErrorMsg. (RequireNoArgError tag notVoidErrorMsg, CustomErrorHasDoc tag) => Label tag -> IndigoM r Source #
failUnexpected_ :: MText -> IndigoM r Source #
assertCustom :: forall tag err errEx ex. (err ~ ErrorArg tag, CustomErrorHasDoc tag, NiceConstant err, IsExpr errEx err, IsExpr ex Bool) => Label tag -> errEx -> ex -> IndigoM () Source #
assertCustom_ :: forall tag notVoidErrorMsg ex. (RequireNoArgError tag notVoidErrorMsg, CustomErrorHasDoc tag, IsExpr ex Bool) => Label tag -> ex -> IndigoM () Source #
Comments
comment :: CommentType -> IndigoM () Source #
Add a comment in a generated Michelson code
justComment :: Text -> IndigoM () Source #
Add a comment in a generated Michelson code
commentAroundFun :: Text -> IndigoM a -> IndigoM a Source #
Add a comment before and after the given Indigo function code. The first argument is the name of the function.
commentAroundStmt :: Text -> IndigoM a -> IndigoM a Source #
Add a comment before and after the given Indigo statement code. The first argument is the name of the statement.
Blocks
type IndigoFunction ret = IndigoM (RetVars ret) Source #
Utility type for an IndigoM
that adds one element to the stack and returns
a variable pointing at it.
type IndigoProcedure = IndigoM () Source #
Utility type for an IndigoM
that does not modify the stack (only the
values in it) and returns nothing.
type IndigoEntrypoint param = param -> IndigoProcedure Source #
Helpers
liftIndigoState :: (forall inp. SomeIndigoState inp a) -> IndigoM a Source #