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

Indigo.Frontend.Statement

Description

StatementF functor datatype for Freer monad

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 a) -> StatementF freer a

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

NewVar :: KnownValue x => Expr x -> StatementF freer (Var x) 
SetVar :: 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 () 
LambdaPure1Call :: (ExecuteLambdaPure1C arg res, CreateLambdaPure1C arg res, Typeable res) => String -> (Var arg -> freer res) -> Expr arg -> StatementF freer (RetVars res)

Pure lambda

Lambda1Call :: (ExecuteLambda1C st arg res, CreateLambda1C st arg res, Typeable res) => Proxy st -> String -> (Var arg -> freer res) -> Expr arg -> StatementF freer (RetVars res)

Default lambda which can modify storage

LambdaEff1Call :: (ExecuteLambdaEff1C st arg res, CreateLambdaEff1C st arg res, Typeable res) => Proxy st -> String -> (Var arg -> freer res) -> Expr arg -> StatementF freer (RetVars res)

Lambda which can modify storage and emit operations

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 :: DocGrouping -> freer () -> StatementF freer () 
ContractGeneral :: freer () -> StatementF freer () 
FinalizeParamCallingDoc :: (NiceParameterFull cp, RequireSumType cp, HasCallStack) => (Var cp -> freer x) -> Expr cp -> StatementF freer x 
TransferTokens :: (NiceParameter p, HasSideEffects) => Expr p -> Expr Mutez -> Expr (ContractRef p) -> StatementF freer () 
SetDelegate :: HasSideEffects => Expr (Maybe KeyHash) -> StatementF freer () 
CreateContract :: (IsObject st, NiceStorage st, NiceParameterFull param, HasSideEffects) => Contract param st -> Expr (Maybe KeyHash) -> Expr Mutez -> Expr st -> StatementF freer (Var Address) 
ContractCalling :: (HasEntrypointArg cp epRef epArg, ToTAddress cp addr, ToT addr ~ ToT Address, KnownValue epArg) => Proxy cp -> epRef -> Expr addr -> StatementF freer (Var (Maybe (ContractRef epArg))) 
FailWith :: KnownValue a => Expr a -> StatementF freer r 
Assert :: IsError x => x -> Expr Bool -> StatementF freer () 
FailCustom :: (err ~ ErrorArg tag, CustomErrorHasDoc tag, NiceConstant err) => Label tag -> Expr err -> StatementF freer r 

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 :: (CaseArrow name (Var x -> IndigoAnyOut x ret) (IndigoCaseClauseL ret ('CaseClauseParam ctor ('OneField x))), 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)) 

type CaseCommonF f dt ret clauses = (InstrCaseC dt, RMap (CaseClauses dt), clauses ~ Rec (f ret) (CaseClauses dt), ScopeCodeGen ret) Source #