indigo-0.6.0: Convenient imperative eDSL over Lorentz.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Indigo.Frontend.Internal.Statement

Description

StatementF functor datatype for Freer monad

This defines the AST of the syntactical constructs of Indigo.

Despite being a part of the "front-end", this module is considered internal implementation detail. It's not intended to be used by the end-user and hence is not re-exported.

Synopsis

Documentation

data StatementF (freer :: Type -> Type) a where Source #

StatementF functor for Freer monad.

The constructors correspond to every Indigo statement that has expressions (Expr x) in its signature.

The ones that don't take expressions are compiled directly to IndigoState (and kept in LiftIndigoState), because they won't be taken into consideration by an optimizer anyway.

One more detail about StatementF is that it takes a cont type parameter, which is basically IndigoM (freer monad), to avoid cyclic dependencies. cont is needed to support statements which have recursive structure (like: if, while, case, etc).

Constructors

LiftIndigoState :: (forall inp. SomeIndigoState inp) -> StatementF freer ()

Direct injection of IndigoState of statements which are not going to be analyzed by optimizer.

CalledFrom :: CallStack -> freer a -> StatementF freer a

Constructor wrapper which holds IndigoM function among with the callstack of caller side.

The another option could be to add HasCallStack to Instr constructor of Program but this would have held only a CallStack of separate primitive statement (unlike updateStorageField, etc). The idea is to be able to have correspondence between original Indigo code and the generated Michelson assembler and vice versa to perform quick navigation and analyze, so it's better to have call stack for non-primitive frontend statements.

NewVar :: KnownValue x => Expr x -> StatementF freer (Var x) 
SetVar :: KnownValue x => Var x -> Expr x -> StatementF freer () 
VarModification :: (IsObject x, KnownValue y) => ([y, x] :-> '[x]) -> Var x -> Expr y -> StatementF freer () 
SetField :: (IsObject dt, IsObject ftype, HasField dt fname ftype) => Var dt -> Label fname -> Expr ftype -> StatementF cont () 
LambdaCall1 :: LambdaKind st arg res extra -> String -> (Var arg -> freer res) -> Expr arg -> StatementF freer (RetVars res) 
Scope :: ScopeCodeGen a => freer a -> StatementF freer (RetVars a) 
If :: IfConstraint a b => Expr Bool -> freer a -> freer b -> StatementF freer (RetVars a) 
IfSome :: (IfConstraint a b, KnownValue x) => Expr (Maybe x) -> (Var x -> freer a) -> freer b -> StatementF freer (RetVars a) 
IfRight :: (IfConstraint a b, KnownValue x, KnownValue y) => Expr (Either y x) -> (Var x -> freer a) -> (Var y -> freer b) -> StatementF freer (RetVars a) 
IfCons :: (IfConstraint a b, KnownValue x) => Expr (List x) -> (Var x -> Var (List x) -> freer a) -> freer b -> StatementF freer (RetVars a) 
Case :: CaseCommonF (IndigoMCaseClauseL freer) dt ret clauses => Expr dt -> clauses -> StatementF freer (RetVars ret) 
EntryCase :: (CaseCommonF (IndigoMCaseClauseL freer) dt ret clauses, DocumentEntrypoints entrypointKind dt) => Proxy entrypointKind -> Expr dt -> clauses -> StatementF freer (RetVars ret) 
EntryCaseSimple :: (CaseCommonF (IndigoMCaseClauseL freer) cp ret clauses, DocumentEntrypoints PlainEntrypointsKind cp, NiceParameterFull cp, RequireFlatParamEps cp) => Expr cp -> clauses -> StatementF freer (RetVars ret) 
While :: Expr Bool -> freer () -> StatementF freer () 
WhileLeft :: (KnownValue x, KnownValue y) => Expr (Either y x) -> (Var y -> freer ()) -> StatementF freer (Var x) 
ForEach :: (IterOpHs a, KnownValue (IterOpElHs a)) => Expr a -> (Var (IterOpElHs a) -> freer ()) -> StatementF freer () 
ContractName :: Text -> freer () -> StatementF freer () 
DocGroup :: DocItem di => (SubDoc -> di) -> freer () -> StatementF freer () 
ContractGeneral :: freer () -> StatementF freer () 
FinalizeParamCallingDoc :: (NiceParameterFull cp, RequireSumType cp, HasCallStack) => (Var cp -> freer ()) -> Expr cp -> StatementF freer () 
TransferTokens :: (NiceParameter p, HasSideEffects, IsNotInView) => Expr p -> Expr Mutez -> Expr (ContractRef p) -> StatementF freer () 
SetDelegate :: (HasSideEffects, IsNotInView) => Expr (Maybe KeyHash) -> StatementF freer () 
CreateContract :: (IsObject st, NiceStorage st, NiceParameterFull param, HasSideEffects, NiceViewsDescriptor vd, Typeable vd, IsNotInView) => Contract param st vd -> Expr (Maybe KeyHash) -> Expr Mutez -> Expr st -> StatementF freer (Var Address) 
SelfCalling :: (NiceParameterFull p, KnownValue (GetEntrypointArgCustom p mname), IsoValue (ContractRef (GetEntrypointArgCustom p mname)), IsNotInView) => Proxy p -> EntrypointRef mname -> StatementF freer (Var (ContractRef (GetEntrypointArgCustom p mname))) 
ContractCalling :: (HasEntrypointArg cp epRef epArg, ToTAddress cp vd addr, ToT addr ~ ToT Address, KnownValue epArg, IsoValue (ContractRef epArg)) => Proxy (cp, vd) -> epRef -> Expr addr -> StatementF freer (Var (Maybe (ContractRef epArg))) 
Emit :: (HasSideEffects, NicePackedValue a, HasAnnotation a) => FieldAnn -> Expr a -> StatementF freer () 
Fail :: ReturnableValue ret => Proxy ret -> (forall inp. SomeIndigoState inp) -> StatementF freer (RetVars ret) 
FailOver :: ReturnableValue ret => Proxy ret -> (forall inp. Expr a -> SomeIndigoState inp) -> Expr a -> StatementF freer (RetVars ret) 

type IfConstraint a b = (ScopeCodeGen a, ScopeCodeGen b, CompareBranchesResults (RetExprs a) (RetExprs b), RetVars a ~ RetVars b, RetOutStack a ~ RetOutStack b) Source #

data IndigoMCaseClauseL freer ret (param :: CaseClauseParam) where Source #

Analogous datatype as IndigoCaseClauseL from Indigo.Backend.Case

Constructors

OneFieldIndigoMCaseClauseL :: (name ~ AppendSymbol "c" ctor, KnownValue x, ScopeCodeGen retBr, ret ~ RetExprs retBr, RetOutStack ret ~ RetOutStack retBr) => Label name -> (Var x -> freer retBr) -> IndigoMCaseClauseL freer ret ('CaseClauseParam ctor ('OneField x)) 

data LambdaKind st arg res extra where Source #

Describes kind of lambda: pure, modifying storage, effectfull

Constructors

PureLambda :: (ExecuteLambdaPure1C arg res, CreateLambda1CGeneric '[] arg res, Typeable res) => LambdaKind st arg res '[] 
StorageLambda :: (ExecuteLambda1C st arg res, CreateLambda1CGeneric '[st] arg res, Typeable res) => Proxy st -> LambdaKind st arg res '[st] 
EffLambda :: (ExecuteLambdaEff1C st arg res, CreateLambda1CGeneric '[st, Ops] arg res, Typeable res) => Proxy st -> LambdaKind st arg res '[st, Ops] 

withLambdaKind :: LambdaKind st arg res extra -> ((ScopeCodeGen res, KnownValue arg, Typeable res, CreateLambda1CGeneric extra arg res) => r) -> r Source #

Provide common constraints that are presented in all constructors of LambdaKind