Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Instruction
datatype.
Synopsis
- type Block = [Instruction]
- data Instruction where
- LiftIndigoState :: (forall inp. SomeIndigoState inp) -> Instruction
- Comment :: Text -> Instruction
- AssignVar :: KnownValue x => Var x -> Expr x -> Instruction
- SetVar :: KnownValue x => Var x -> Expr x -> Instruction
- VarModification :: (IsObject x, KnownValue y) => ([y, x] :-> '[x]) -> Var x -> Expr y -> Instruction
- SetField :: (HasField store fname ftype, IsObject store, IsObject ftype) => Var store -> Label fname -> Expr ftype -> Instruction
- LambdaCall1 :: LambdaKind st arg ret extra -> String -> Expr arg -> Var arg -> Block -> ret -> RetVars ret -> Instruction
- CreateLambda1 :: CreateLambda1CGeneric extra arg ret => StackVars (arg ': extra) -> Var arg -> Block -> ret -> Var (Lambda1Generic extra arg ret) -> Instruction
- ExecLambda1 :: LambdaKind st arg ret extra -> Proxy ret -> Expr arg -> Var (Lambda1Generic extra arg ret) -> RetVars ret -> Instruction
- Scope :: ScopeCodeGen ret => Block -> ret -> RetVars ret -> Instruction
- If :: IfConstraint a b => Expr Bool -> Block -> a -> Block -> b -> RetVars a -> Instruction
- IfSome :: (IfConstraint a b, KnownValue x) => Expr (Maybe x) -> Var x -> Block -> a -> Block -> b -> RetVars a -> Instruction
- IfRight :: (IfConstraint a b, KnownValue r, KnownValue l) => Expr (Either l r) -> Var r -> Block -> a -> Var l -> Block -> b -> RetVars a -> Instruction
- IfCons :: (IfConstraint a b, KnownValue x) => Expr (List x) -> Var x -> Var (List x) -> Block -> a -> Block -> b -> RetVars a -> Instruction
- Case :: CaseCommon dt ret clauses => Expr dt -> clauses -> RetVars ret -> Instruction
- EntryCase :: (CaseCommon dt ret clauses, DocumentEntrypoints entryPointKind dt) => Proxy entryPointKind -> Expr dt -> clauses -> RetVars ret -> Instruction
- EntryCaseSimple :: (CaseCommon dt ret clauses, DocumentEntrypoints PlainEntrypointsKind dt, NiceParameterFull dt, RequireFlatParamEps dt) => Expr dt -> clauses -> RetVars ret -> Instruction
- While :: Expr Bool -> Block -> Instruction
- WhileLeft :: (KnownValue l, KnownValue r) => Expr (Either l r) -> Var l -> Block -> Var r -> Instruction
- ForEach :: (IterOpHs a, KnownValue (IterOpElHs a)) => Expr a -> Var (IterOpElHs a) -> Block -> Instruction
- ContractName :: Text -> Block -> Instruction
- DocGroup :: forall di. DocItem di => (SubDoc -> di) -> Block -> Instruction
- ContractGeneral :: Block -> Instruction
- FinalizeParamCallingDoc :: (NiceParameterFull cp, RequireSumType cp) => Var cp -> Block -> Expr cp -> Instruction
- TransferTokens :: (NiceParameter p, HasSideEffects, IsNotInView) => Expr p -> Expr Mutez -> Expr (ContractRef p) -> Instruction
- SetDelegate :: (HasSideEffects, IsNotInView) => Expr (Maybe KeyHash) -> Instruction
- CreateContract :: (HasSideEffects, NiceStorage s, NiceParameterFull p, NiceViewsDescriptor vd, Typeable vd, IsNotInView) => Contract p s vd -> Expr (Maybe KeyHash) -> Expr Mutez -> Expr s -> Var Address -> Instruction
- SelfCalling :: (NiceParameterFull p, KnownValue (GetEntrypointArgCustom p mname), IsoValue (ContractRef (GetEntrypointArgCustom p mname)), IsNotInView) => Proxy p -> EntrypointRef mname -> Var (ContractRef (GetEntrypointArgCustom p mname)) -> Instruction
- ContractCalling :: (HasEntrypointArg cp epRef epArg, ToTAddress cp vd addr, ToT addr ~ ToT Address, KnownValue epArg, IsoValue (ContractRef epArg)) => Proxy (cp, vd) -> epRef -> Expr addr -> Var (Maybe (ContractRef epArg)) -> Instruction
- Emit :: (HasSideEffects, NicePackedValue a, HasAnnotation a) => FieldAnn -> Expr a -> Instruction
- Fail :: (forall inp. SomeIndigoState inp) -> Instruction
- FailOver :: (forall inp. Expr a -> SomeIndigoState inp) -> Expr a -> Instruction
- data IndigoSeqCaseClause ret (param :: CaseClauseParam) where
- OneFieldIndigoSeqCaseClause :: AppendSymbol "c" ctor ~ name => Label name -> CaseBranch x ret -> IndigoSeqCaseClause ret ('CaseClauseParam ctor ('OneField x))
- data CaseBranch x ret where
- CaseBranch :: (KnownValue x, ScopeCodeGen retBr, ret ~ RetExprs retBr, RetOutStack ret ~ RetOutStack retBr) => Var x -> Block -> retBr -> CaseBranch x ret
- newtype SequentialHooks = SequentialHooks {
- shStmtHook :: CallStack -> Block -> State InstrCollector ()
- data InstrCollector = InstrCollector {}
- stmtHookL :: Lens' SequentialHooks (CallStack -> Block -> State InstrCollector ())
Documentation
type Block = [Instruction] Source #
Simple synonym for a list of Instruction
data Instruction where Source #
Data type representing an instruction.
Differently from the frontend this is not used to build a Monad of some kind, it is instead based on having as argument the variable to associate with the resulting value (if any).
This is combined in simple lists, named Block
, and it is intended to be
easily altered, this is because these are used as the intermediate representation
between the frontend and the backend, where optimizations can occur.
LiftIndigoState :: (forall inp. SomeIndigoState inp) -> Instruction | |
Comment :: Text -> Instruction | |
AssignVar :: KnownValue x => Var x -> Expr x -> Instruction | |
SetVar :: KnownValue x => Var x -> Expr x -> Instruction | |
VarModification :: (IsObject x, KnownValue y) => ([y, x] :-> '[x]) -> Var x -> Expr y -> Instruction | |
SetField :: (HasField store fname ftype, IsObject store, IsObject ftype) => Var store -> Label fname -> Expr ftype -> Instruction | |
LambdaCall1 | |
| |
CreateLambda1 | |
| |
ExecLambda1 | |
| |
Scope | |
| |
If | |
| |
IfSome | |
| |
IfRight | |
| |
IfCons | |
| |
Case | |
| |
EntryCase | |
| |
EntryCaseSimple | |
| |
While | |
| |
WhileLeft | |
| |
ForEach | |
| |
ContractName :: Text -> Block -> Instruction | |
DocGroup :: forall di. DocItem di => (SubDoc -> di) -> Block -> Instruction | |
ContractGeneral :: Block -> Instruction | |
FinalizeParamCallingDoc :: (NiceParameterFull cp, RequireSumType cp) => Var cp -> Block -> Expr cp -> Instruction | |
TransferTokens :: (NiceParameter p, HasSideEffects, IsNotInView) => Expr p -> Expr Mutez -> Expr (ContractRef p) -> Instruction | |
SetDelegate :: (HasSideEffects, IsNotInView) => Expr (Maybe KeyHash) -> Instruction | |
CreateContract | |
| |
SelfCalling | |
| |
ContractCalling | |
| |
Emit :: (HasSideEffects, NicePackedValue a, HasAnnotation a) => FieldAnn -> Expr a -> Instruction | |
Fail :: (forall inp. SomeIndigoState inp) -> Instruction | |
FailOver :: (forall inp. Expr a -> SomeIndigoState inp) -> Expr a -> Instruction |
data IndigoSeqCaseClause ret (param :: CaseClauseParam) where Source #
Analogous datatype as IndigoCaseClauseL
and IndigoMCaseClauseL
.
OneFieldIndigoSeqCaseClause :: AppendSymbol "c" ctor ~ name => Label name -> CaseBranch x ret -> IndigoSeqCaseClause ret ('CaseClauseParam ctor ('OneField x)) |
data CaseBranch x ret where Source #
Representation of a branch of a generic case-like Instruction
.
CaseBranch | |
|
Translations
newtype SequentialHooks Source #
SequentialHooks | |
|
Instances
Monoid SequentialHooks Source # | |
Defined in Indigo.Compilation.Sequential.Types mappend :: SequentialHooks -> SequentialHooks -> SequentialHooks # mconcat :: [SequentialHooks] -> SequentialHooks # | |
Semigroup SequentialHooks Source # | |
Defined in Indigo.Compilation.Sequential.Types (<>) :: SequentialHooks -> SequentialHooks -> SequentialHooks # sconcat :: NonEmpty SequentialHooks -> SequentialHooks # stimes :: Integral b => b -> SequentialHooks -> SequentialHooks # |
data InstrCollector Source #
Data type internally used to collect Instruction
s from IndigoM
stmtHookL :: Lens' SequentialHooks (CallStack -> Block -> State InstrCollector ()) Source #