zeolite-lang-0.24.1.0: Zeolite is a statically-typed, general-purpose programming language.
Safe HaskellSafe
LanguageHaskell2010

Compilation.CompilerState

Documentation

data CleanupBlock c s Source #

Instances

Instances details
(Show s, Show c) => Show (CleanupBlock c s) Source # 
Instance details

Defined in Compilation.CompilerState

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 #

ccSelfType :: a -> m TypeInstance Source #

ccAllFilters :: a -> m ParamFilters Source #

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

ccAddRequired :: 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 -> m () Source #

ccGetVariable :: a -> UsedVariable c -> m (VariableValue c) Source #

ccAddVariable :: a -> UsedVariable c -> VariableValue c -> m a Source #

ccSetDeferred :: a -> UsedVariable c -> m a Source #

ccSetReadOnly :: a -> UsedVariable c -> m a Source #

ccSetHidden :: a -> UsedVariable c -> m a Source #

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

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

ccGetOutput :: a -> m s Source #

ccClearOutput :: a -> m a Source #

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

ccAddUsed :: a -> UsedVariable c -> m a Source #

ccInheritUsed :: a -> a -> m a Source #

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

ccInheritDeferred :: a -> DeferVariable c -> 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 #

ccSetJumpType :: a -> [c] -> JumpType -> m a Source #

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

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

ccStartCleanup :: a -> [c] -> m a Source #

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

ccGetCleanup :: a -> JumpType -> m (CleanupBlock c s) Source #

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

ccReserveExprMacro :: a -> [c] -> MacroName -> m a Source #

ccReleaseExprMacro :: a -> [c] -> MacroName -> m a Source #

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

ccGetNoTrace :: a -> m Bool Source #

ccGetTestsOnly :: a -> m Bool Source #

ccAddTrace :: a -> String -> m a Source #

ccGetTraces :: a -> m [String] Source #

ccCanForward :: a -> [ParamName] -> [VariableName] -> m Bool Source #

ccDelegateArgs :: a -> m (Positional (Maybe (CallArgLabel c), VariableName)) Source #

Instances

Instances details
(Show c, CollectErrorsM 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 #

ccSelfType :: ProcedureContext c -> m TypeInstance Source #

ccAllFilters :: ProcedureContext c -> m ParamFilters Source #

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

ccAddRequired :: 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 -> m () Source #

ccGetVariable :: ProcedureContext c -> UsedVariable c -> m (VariableValue c) Source #

ccAddVariable :: ProcedureContext c -> UsedVariable c -> VariableValue c -> m (ProcedureContext c) Source #

ccSetDeferred :: ProcedureContext c -> UsedVariable c -> m (ProcedureContext c) Source #

ccSetReadOnly :: ProcedureContext c -> UsedVariable c -> m (ProcedureContext c) Source #

ccSetHidden :: ProcedureContext c -> UsedVariable c -> m (ProcedureContext c) Source #

ccCheckVariableInit :: ProcedureContext c -> [UsedVariable c] -> 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 #

ccAddUsed :: ProcedureContext c -> UsedVariable c -> m (ProcedureContext c) Source #

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

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

ccInheritDeferred :: ProcedureContext c -> DeferVariable 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 #

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

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

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

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

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

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

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

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

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

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

ccGetNoTrace :: ProcedureContext c -> m Bool Source #

ccGetTestsOnly :: ProcedureContext c -> m Bool Source #

ccAddTrace :: ProcedureContext c -> String -> m (ProcedureContext c) Source #

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

ccCanForward :: ProcedureContext c -> [ParamName] -> [VariableName] -> m Bool Source #

ccDelegateArgs :: ProcedureContext c -> m (Positional (Maybe (CallArgLabel c), VariableName)) Source #

data CompiledData s Source #

Instances

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

Defined in Compilation.CompilerState

Semigroup s => Semigroup (CompiledData s) Source # 
Instance details

Defined in Compilation.CompilerState

type CompilerState a m = StateT a m Source #

newtype DeferVariable c Source #

Instances

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

Defined in Compilation.CompilerState

data LoopSetup s Source #

Constructors

LoopSetup 

Fields

NotInLoop 

data MemberValue c Source #

Constructors

MemberValue 

Instances

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

Defined in Compilation.CompilerState

data ReturnVariable Source #

Constructors

ReturnVariable 

Instances

Instances details
Show ReturnVariable Source # 
Instance details

Defined in Compilation.CompilerState

data UsedVariable c Source #

Constructors

UsedVariable 

Fields

Instances

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

Defined in Compilation.CompilerState

Eq c => Eq (UsedVariable c) Source # 
Instance details

Defined in Compilation.CompilerState

Ord c => Ord (UsedVariable c) Source # 
Instance details

Defined in Compilation.CompilerState

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