indigo-0.2.1: Convenient imperative eDSL over Lorentz.
Safe HaskellNone
LanguageHaskell2010

Indigo.Backend

Description

Strictly typed statements of Indigo language.

Synopsis

Documentation

Loop

forEach :: (IterOpHs a, KnownValue (IterOpElHs a)) => Expr a -> (Var (IterOpElHs a) -> IndigoState (IterOpElHs a & inp) xs ()) -> IndigoState inp inp () Source #

For statements to iterate over container.

while :: Expr Bool -> IndigoState inp xs () -> IndigoState inp inp () Source #

While statement. The same rule about releasing.

whileLeft :: (KnownValue l, KnownValue r) => Expr (Either l r) -> (Var l -> IndigoState (l & inp) xs ()) -> IndigoState inp (r & inp) (Var r) Source #

Contract call

contractCalling :: forall cp inp epRef epArg addr. (HasEntrypointArg cp epRef epArg, ToTAddress cp addr, ToT addr ~ ToT Address, KnownValue epArg) => epRef -> Expr addr -> IndigoState inp (Maybe (ContractRef epArg) & inp) (Var (Maybe (ContractRef epArg))) Source #

Documentation

doc :: DocItem di => di -> IndigoState s s () Source #

Put a document item.

docGroup :: DocGrouping -> IndigoState i o () -> IndigoState i o () Source #

Group documentation built in the given piece of code into 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 -> IndigoState i o () -> IndigoState i o () Source #

Give a name to given contract. Apply it to the whole contract code.

finalizeParamCallingDoc :: (NiceParameterFull cp, RequireSumType cp, HasCallStack) => (Var cp -> IndigoState (cp & inp) out x) -> Expr cp -> IndigoState inp out x Source #

Indigo version for the function of the same name from Lorentz.

contractGeneral :: IndigoState i o () -> IndigoState i o () Source #

Attach general info to given contract.

contractGeneralDefault :: IndigoState s s () Source #

Attach default general info to the contract documentation.

Side-effects

Functions, Procedures and Scopes

scope :: forall a inp out. ScopeCodeGen a => IndigoState inp out a -> IndigoState inp (RetOutStack a ++ inp) (RetVars a) Source #

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