Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
data CompiledData s Source #
Constructors
CompiledData | |
Fields
|
Instances
Monoid s => Mergeable (CompiledData s) Source # | |
Defined in Compilation.CompilerState Methods mergeAny :: Foldable f => f (CompiledData s) -> CompiledData s Source # mergeAll :: Foldable f => f (CompiledData s) -> CompiledData s Source # |
type CompilerState a m = StateT a m Source #
type ExpressionType = Positional ValueType Source #
data MemberValue c Source #
Constructors
MemberValue | |
Fields
|
Instances
Show c => Show (MemberValue c) Source # | |
Defined in Compilation.CompilerState Methods showsPrec :: Int -> MemberValue c -> ShowS # show :: MemberValue c -> String # showList :: [MemberValue c] -> ShowS # |
data ReturnVariable Source #
Constructors
ReturnVariable | |
Instances
Show ReturnVariable Source # | |
Defined in Compilation.CompilerState Methods showsPrec :: Int -> ReturnVariable -> ShowS # show :: ReturnVariable -> String # showList :: [ReturnVariable] -> ShowS # |
(<???) :: CompileErrorM m => CompilerState a m b -> String -> CompilerState a m b Source #
(???>) :: CompileErrorM m => String -> CompilerState a m b -> CompilerState a m b Source #
csAddVariable :: CompilerContext c m s a => [c] -> VariableName -> VariableValue c -> CompilerState a m () Source #
csAllFilters :: CompilerContext c m s a => CompilerState a m ParamFilters Source #
csCheckValueInit :: CompilerContext c m s a => [c] -> TypeInstance -> ExpressionType -> Positional GeneralInstance -> CompilerState a m () Source #
csCheckVariableInit :: CompilerContext c m s a => [c] -> VariableName -> CompilerState a m () Source #
csClearOutput :: CompilerContext c m s a => CompilerState a m () Source #
csCurrentScope :: CompilerContext c m s a => CompilerState a m SymbolScope Source #
csExprLookup :: CompilerContext c m s a => [c] -> String -> CompilerState a m (Expression c) Source #
csGetCategoryFunction :: CompilerContext c m s a => [c] -> Maybe CategoryName -> FunctionName -> CompilerState a m (ScopedFunction c) Source #
csGetCleanup :: CompilerContext c m s a => CompilerState a m (CleanupSetup a s) Source #
csGetLoop :: CompilerContext c m s a => CompilerState a m (LoopSetup s) Source #
csGetNoTrace :: CompilerContext c m s a => CompilerState a m Bool Source #
csGetOutput :: CompilerContext c m s a => CompilerState a m s Source #
csGetParamScope :: CompilerContext c m s a => ParamName -> CompilerState a m SymbolScope Source #
csGetTypeFunction :: CompilerContext c m s a => [c] -> Maybe GeneralInstance -> FunctionName -> CompilerState a m (ScopedFunction c) Source #
csGetVariable :: CompilerContext c m s a => [c] -> VariableName -> CompilerState a m (VariableValue c) Source #
csInheritReturns :: CompilerContext c m s a => [a] -> CompilerState a m () Source #
csIsNamedReturns :: CompilerContext c m s a => CompilerState a m Bool Source #
csIsUnreachable :: CompilerContext c m s a => CompilerState a m Bool Source #
csPrimNamedReturns :: CompilerContext c m s a => CompilerState a m [ReturnVariable] Source #
csPushCleanup :: CompilerContext c m s a => CleanupSetup a s -> CompilerState a m () Source #
csRegisterReturn :: CompilerContext c m s a => [c] -> Maybe ExpressionType -> CompilerState a m () Source #
csRequiresTypes :: CompilerContext c m s a => Set CategoryName -> CompilerState a m () Source #
csResolver :: CompilerContext c m s a => CompilerState a m AnyTypeResolver Source #
csSameType :: CompilerContext c m s a => TypeInstance -> CompilerState a m Bool Source #
csSetNoReturn :: CompilerContext c m s a => CompilerState a m () Source #
csSetNoTrace :: CompilerContext c m s a => Bool -> CompilerState a m () Source #
csStartLoop :: CompilerContext c m s a => LoopSetup s -> CompilerState a m () Source #
csUpdateAssigned :: CompilerContext c m s a => VariableName -> CompilerState a m () Source #
csWrite :: CompilerContext c m s a => s -> CompilerState a m () Source #
getCleanContext :: CompilerContext c m s a => CompilerState a m a Source #
resetBackgroundStateT :: CompileErrorM m => CompilerState a m b -> CompilerState a m b Source #
runDataCompiler :: CompilerContext c m s a => CompilerState a m b -> a -> m (CompiledData s) Source #
Orphan instances
Show c => Show (VariableValue c) Source # | |
Methods showsPrec :: Int -> VariableValue c -> ShowS # show :: VariableValue c -> String # showList :: [VariableValue c] -> ShowS # |