zeolite-lang-0.7.0.2: Zeolite is a statically-typed, general-purpose programming language.

Safe HaskellSafe
LanguageHaskell2010

Compilation.CompilerState

Contents

Documentation

data CleanupSetup a s Source #

Constructors

CleanupSetup 

Fields

class (Functor m, Monad m) => CompilerContext c m s a | a -> c s where Source #

Methods

ccCurrentScope :: a -> m SymbolScope Source #

ccResolver :: a -> m AnyTypeResolver Source #

ccSameType :: a -> TypeInstance -> m Bool Source #

ccAllFilters :: a -> m ParamFilters Source #

ccGetParamScope :: a -> ParamName -> m SymbolScope Source #

ccRequiresTypes :: a -> Set CategoryName -> m a Source #

ccGetRequired :: a -> m (Set CategoryName) Source #

ccGetCategoryFunction :: a -> [c] -> Maybe CategoryName -> FunctionName -> m (ScopedFunction c) Source #

ccGetTypeFunction :: a -> [c] -> Maybe GeneralInstance -> FunctionName -> m (ScopedFunction c) Source #

ccCheckValueInit :: a -> [c] -> TypeInstance -> ExpressionType -> Positional GeneralInstance -> m () Source #

ccGetVariable :: a -> [c] -> VariableName -> m (VariableValue c) Source #

ccAddVariable :: a -> [c] -> VariableName -> VariableValue c -> m a Source #

ccCheckVariableInit :: a -> [c] -> VariableName -> m () Source #

ccWrite :: a -> s -> m a Source #

ccGetOutput :: a -> m s Source #

ccClearOutput :: a -> m a Source #

ccUpdateAssigned :: a -> VariableName -> m a Source #

ccInheritReturns :: a -> [a] -> m a Source #

ccRegisterReturn :: a -> [c] -> Maybe ExpressionType -> m a Source #

ccPrimNamedReturns :: a -> m [ReturnVariable] Source #

ccIsUnreachable :: a -> m Bool Source #

ccIsNamedReturns :: a -> m Bool Source #

ccSetNoReturn :: a -> m a Source #

ccStartLoop :: a -> LoopSetup s -> m a Source #

ccGetLoop :: a -> m (LoopSetup s) Source #

ccPushCleanup :: a -> CleanupSetup a s -> m a Source #

ccGetCleanup :: a -> m (CleanupSetup a s) Source #

ccExprLookup :: a -> [c] -> String -> m (Expression c) Source #

ccSetNoTrace :: a -> Bool -> m a Source #

ccGetNoTrace :: a -> m Bool Source #

Instances
(Show c, MergeableM m, CompileErrorM m) => CompilerContext c m [String] (ProcedureContext c) Source # 
Instance details

Defined in Compilation.ProcedureContext

Methods

ccCurrentScope :: ProcedureContext c -> m SymbolScope Source #

ccResolver :: ProcedureContext c -> m AnyTypeResolver Source #

ccSameType :: ProcedureContext c -> TypeInstance -> m Bool Source #

ccAllFilters :: ProcedureContext c -> m ParamFilters Source #

ccGetParamScope :: ProcedureContext c -> ParamName -> m SymbolScope Source #

ccRequiresTypes :: ProcedureContext c -> Set CategoryName -> m (ProcedureContext c) Source #

ccGetRequired :: ProcedureContext c -> m (Set CategoryName) Source #

ccGetCategoryFunction :: ProcedureContext c -> [c] -> Maybe CategoryName -> FunctionName -> m (ScopedFunction c) Source #

ccGetTypeFunction :: ProcedureContext c -> [c] -> Maybe GeneralInstance -> FunctionName -> m (ScopedFunction c) Source #

ccCheckValueInit :: ProcedureContext c -> [c] -> TypeInstance -> ExpressionType -> Positional GeneralInstance -> m () Source #

ccGetVariable :: ProcedureContext c -> [c] -> VariableName -> m (VariableValue c) Source #

ccAddVariable :: ProcedureContext c -> [c] -> VariableName -> VariableValue c -> m (ProcedureContext c) Source #

ccCheckVariableInit :: ProcedureContext c -> [c] -> VariableName -> m () Source #

ccWrite :: ProcedureContext c -> [String] -> m (ProcedureContext c) Source #

ccGetOutput :: ProcedureContext c -> m [String] Source #

ccClearOutput :: ProcedureContext c -> m (ProcedureContext c) Source #

ccUpdateAssigned :: ProcedureContext c -> VariableName -> m (ProcedureContext c) Source #

ccInheritReturns :: ProcedureContext c -> [ProcedureContext c] -> m (ProcedureContext c) Source #

ccRegisterReturn :: ProcedureContext c -> [c] -> Maybe ExpressionType -> m (ProcedureContext c) Source #

ccPrimNamedReturns :: ProcedureContext c -> m [ReturnVariable] Source #

ccIsUnreachable :: ProcedureContext c -> m Bool Source #

ccIsNamedReturns :: ProcedureContext c -> m Bool Source #

ccSetNoReturn :: ProcedureContext c -> m (ProcedureContext c) Source #

ccStartLoop :: ProcedureContext c -> LoopSetup [String] -> m (ProcedureContext c) Source #

ccGetLoop :: ProcedureContext c -> m (LoopSetup [String]) Source #

ccPushCleanup :: ProcedureContext c -> CleanupSetup (ProcedureContext c) [String] -> m (ProcedureContext c) Source #

ccGetCleanup :: ProcedureContext c -> m (CleanupSetup (ProcedureContext c) [String]) Source #

ccExprLookup :: ProcedureContext c -> [c] -> String -> m (Expression c) Source #

ccSetNoTrace :: ProcedureContext c -> Bool -> m (ProcedureContext c) Source #

ccGetNoTrace :: ProcedureContext c -> m Bool Source #

data CompiledData s Source #

Constructors

CompiledData 
Instances
Monoid s => Mergeable (CompiledData s) Source # 
Instance details

Defined in Compilation.CompilerState

type CompilerState a m = StateT a m Source #

data LoopSetup s Source #

Constructors

LoopSetup 

Fields

NotInLoop 

data MemberValue c Source #

Constructors

MemberValue 
Instances
Show c => Show (MemberValue c) Source # 
Instance details

Defined in Compilation.CompilerState

csWrite :: CompilerContext c m s a => s -> CompilerState a m () Source #

Orphan instances

Show c => Show (VariableValue c) Source # 
Instance details