| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Indigo.Backend
Description
Strictly typed statements of Indigo language.
Synopsis
- module Indigo.Backend.Var
 - module Indigo.Backend.Scope
 - module Indigo.Backend.Lambda
 - module Indigo.Backend.Error
 - module Indigo.Backend.Conditional
 - module Indigo.Backend.Case
 - forEach :: (IterOpHs a, KnownValue (IterOpElHs a)) => Expr a -> Var (IterOpElHs a) -> SomeIndigoState (IterOpElHs a & inp) -> IndigoState inp inp
 - while :: Expr Bool -> SomeIndigoState inp -> IndigoState inp inp
 - whileLeft :: (KnownValue l, KnownValue r) => Expr (Either l r) -> Var l -> SomeIndigoState (l & inp) -> Var r -> IndigoState inp (r & inp)
 - selfCalling :: forall p inp mname. (NiceParameterFull p, KnownValue (GetEntrypointArgCustom p mname)) => EntrypointRef mname -> Var (ContractRef (GetEntrypointArgCustom p mname)) -> IndigoState inp (ContractRef (GetEntrypointArgCustom p mname) & inp)
 - contractCalling :: forall cp inp epRef epArg addr. (HasEntrypointArg cp epRef epArg, ToTAddress cp addr, ToT addr ~ ToT Address, KnownValue epArg) => epRef -> Expr addr -> Var (Maybe (ContractRef epArg)) -> IndigoState inp (Maybe (ContractRef epArg) & inp)
 - doc :: DocItem di => di -> IndigoState s s
 - docGroup :: DocGrouping -> SomeIndigoState i -> SomeIndigoState i
 - docStorage :: forall storage s. TypeHasDoc storage => IndigoState s s
 - contractName :: Text -> SomeIndigoState i -> SomeIndigoState i
 - finalizeParamCallingDoc :: (NiceParameterFull cp, RequireSumType cp, HasCallStack) => Var cp -> SomeIndigoState (cp & inp) -> Expr cp -> SomeIndigoState inp
 - contractGeneral :: SomeIndigoState i -> SomeIndigoState i
 - contractGeneralDefault :: IndigoState s s
 - transferTokens :: (NiceParameter p, HasSideEffects) => Expr p -> Expr Mutez -> Expr (ContractRef p) -> IndigoState inp inp
 - setDelegate :: HasSideEffects => Expr (Maybe KeyHash) -> IndigoState inp inp
 - createContract :: (HasSideEffects, NiceStorage s, NiceParameterFull p) => Contract p s -> Expr (Maybe KeyHash) -> Expr Mutez -> Expr s -> Var Address -> IndigoState inp (Address & inp)
 - scope :: forall ret inp. ScopeCodeGen ret => SomeIndigoState inp -> ret -> RetVars ret -> IndigoState inp (RetOutStack ret ++ inp)
 - comment :: CommentType -> IndigoState i i
 
Documentation
module Indigo.Backend.Var
module Indigo.Backend.Scope
module Indigo.Backend.Lambda
module Indigo.Backend.Error
module Indigo.Backend.Conditional
module Indigo.Backend.Case
Loop
Arguments
| :: (IterOpHs a, KnownValue (IterOpElHs a)) | |
| => Expr a | Expression for the container to traverse  | 
| -> Var (IterOpElHs a) | Variable for the current item (available to the code block)  | 
| -> SomeIndigoState (IterOpElHs a & inp) | Code block to execute over each element of the container  | 
| -> IndigoState inp inp | 
For statements to iterate over a container.
Arguments
| :: Expr Bool | Expression for the control flow  | 
| -> SomeIndigoState inp | Block of code to execute, as long as the expression holds   | 
| -> IndigoState inp inp | 
While statement.
Arguments
| :: (KnownValue l, KnownValue r) | |
| => Expr (Either l r) | Expression for the control flow value  | 
| -> Var l | Variable for the   | 
| -> SomeIndigoState (l & inp) | Code block to execute while the value is   | 
| -> Var r | Variable that will be assigned to the resulting value  | 
| -> IndigoState inp (r & inp) | 
Contract call
Arguments
| :: forall p inp mname. (NiceParameterFull p, KnownValue (GetEntrypointArgCustom p mname)) | |
| => EntrypointRef mname | |
| -> Var (ContractRef (GetEntrypointArgCustom p mname)) | Variable that will be assigned to the resulting   | 
| -> IndigoState inp (ContractRef (GetEntrypointArgCustom p mname) & inp) | 
Arguments
| :: forall cp inp epRef epArg addr. (HasEntrypointArg cp epRef epArg, ToTAddress cp addr, ToT addr ~ ToT Address, KnownValue epArg) | |
| => epRef | |
| -> Expr addr | |
| -> Var (Maybe (ContractRef epArg)) | Variable that will be assigned to the resulting   | 
| -> IndigoState inp (Maybe (ContractRef epArg) & inp) | 
Documentation
doc :: DocItem di => di -> IndigoState s s Source #
Put a document item.
docGroup :: DocGrouping -> SomeIndigoState i -> SomeIndigoState i 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 s. TypeHasDoc storage => IndigoState s s Source #
Insert documentation of the contract storage type. The type should be passed using type applications.
contractName :: Text -> SomeIndigoState i -> SomeIndigoState i Source #
Give a name to the given contract. Apply it to the whole contract code.
finalizeParamCallingDoc :: (NiceParameterFull cp, RequireSumType cp, HasCallStack) => Var cp -> SomeIndigoState (cp & inp) -> Expr cp -> SomeIndigoState inp Source #
Indigo version for the function of the same name from Lorentz.
contractGeneral :: SomeIndigoState i -> SomeIndigoState i Source #
Attach general info to the given contract.
contractGeneralDefault :: IndigoState s s Source #
Attach default general info to the contract documentation.
Side-effects
transferTokens :: (NiceParameter p, HasSideEffects) => Expr p -> Expr Mutez -> Expr (ContractRef p) -> IndigoState inp inp Source #
setDelegate :: HasSideEffects => Expr (Maybe KeyHash) -> IndigoState inp inp Source #
Arguments
| :: (HasSideEffects, NiceStorage s, NiceParameterFull p) | |
| => Contract p s | |
| -> Expr (Maybe KeyHash) | |
| -> Expr Mutez | |
| -> Expr s | |
| -> Var Address | Variable that will be assigned to the resulting   | 
| -> IndigoState inp (Address & inp) | 
Functions, Procedures and Scopes
Arguments
| :: forall ret inp. ScopeCodeGen ret | |
| => SomeIndigoState inp | Code block to execute inside the scope  | 
| -> ret | Return value(s) of the scoped code block  | 
| -> RetVars ret | Variable(s) that will be assigned to the resulting value(s)  | 
| -> IndigoState inp (RetOutStack ret ++ inp) | 
Takes an arbitrary IndigoM and wraps it into an IndigoFunction
 producing a local scope for its execution. Once it executed, all
 non-returned variables are cleaned up so that the stack has only
 returned variables at the top. This also can be interpreted as
 if True then f else nop.
Note, that by default we do not define scope inside indigo functions,
 meaning that once we want to create a new variable or return it from
 a function we need to do it inside scope $ instr construction, for
 example:
f :: IndigoFunction s Natural
f = scope $ do
  *[s]*
  res <- newVar (0 :: Natural)
  *[Natural, s]*
  scope $ do
    _n <- newVar (1 :: Integer)
    *[Integer, Natural, s]
    res += 4
  *[Natural, s]*
  return res
  *[s]*
Comments
comment :: CommentType -> IndigoState i i Source #
Add a comment