Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Compilation.CompilerState
Documentation
data CleanupBlock c s Source #
Constructors
CleanupBlock | |
Fields
|
Instances
(Show s, Show c) => Show (CleanupBlock c s) Source # | |
Defined in Compilation.CompilerState Methods showsPrec :: Int -> CleanupBlock c s -> ShowS # show :: CleanupBlock c s -> String # showList :: [CleanupBlock c s] -> ShowS # |
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
data CompiledData s Source #
Constructors
CompiledData | |
Fields
|
Instances
(Semigroup s, Monoid s) => Monoid (CompiledData s) Source # | |
Defined in Compilation.CompilerState Methods mempty :: CompiledData s # mappend :: CompiledData s -> CompiledData s -> CompiledData s # mconcat :: [CompiledData s] -> CompiledData s # | |
Semigroup s => Semigroup (CompiledData s) Source # | |
Defined in Compilation.CompilerState Methods (<>) :: CompiledData s -> CompiledData s -> CompiledData s # sconcat :: NonEmpty (CompiledData s) -> CompiledData s # stimes :: Integral b => b -> CompiledData s -> CompiledData s # |
type CompilerState a m = StateT a m Source #
newtype DeferVariable c Source #
Constructors
DeferVariable | |
Fields
|
Instances
Show c => Show (DeferVariable c) Source # | |
Defined in Compilation.CompilerState Methods showsPrec :: Int -> DeferVariable c -> ShowS # show :: DeferVariable c -> String # showList :: [DeferVariable c] -> ShowS # |
Constructors
NextStatement | |
JumpContinue | |
JumpBreak | |
JumpReturn | |
JumpImmediateExit | |
JumpMax |
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 # |
data UsedVariable c Source #
Constructors
UsedVariable | |
Fields
|
Instances
Show c => Show (UsedVariable c) Source # | |
Defined in Compilation.CompilerState Methods showsPrec :: Int -> UsedVariable c -> ShowS # show :: UsedVariable c -> String # showList :: [UsedVariable c] -> ShowS # | |
Eq c => Eq (UsedVariable c) Source # | |
Defined in Compilation.CompilerState Methods (==) :: UsedVariable c -> UsedVariable c -> Bool # (/=) :: UsedVariable c -> UsedVariable c -> Bool # | |
Ord c => Ord (UsedVariable c) Source # | |
Defined in Compilation.CompilerState Methods compare :: UsedVariable c -> UsedVariable c -> Ordering # (<) :: UsedVariable c -> UsedVariable c -> Bool # (<=) :: UsedVariable c -> UsedVariable c -> Bool # (>) :: UsedVariable c -> UsedVariable c -> Bool # (>=) :: UsedVariable c -> UsedVariable c -> Bool # max :: UsedVariable c -> UsedVariable c -> UsedVariable c # min :: UsedVariable c -> UsedVariable c -> UsedVariable c # |
addDeferred :: VariableName -> PassedValue c -> DeferVariable c -> DeferVariable c Source #
autoSelfType :: CompilerContext c m s a => CompilerState a m GeneralInstance Source #
branchDeferred :: [DeferVariable c] -> DeferVariable c Source #
checkDeferred :: VariableName -> DeferVariable c -> Bool Source #
concatM :: (Semigroup s, Monoid s, CollectErrorsM m) => [m (CompiledData s)] -> m (CompiledData s) Source #
csAddRequired :: CompilerContext c m s a => Set CategoryName -> CompilerState a m () Source #
csAddTrace :: CompilerContext c m s a => String -> CompilerState a m () Source #
csAddUsed :: CompilerContext c m s a => UsedVariable c -> CompilerState a m () Source #
csAddVariable :: CompilerContext c m s a => UsedVariable c -> VariableValue c -> CompilerState a m () Source #
csAllFilters :: CompilerContext c m s a => CompilerState a m ParamFilters Source #
csCanForward :: CompilerContext c m s a => [ParamName] -> [VariableName] -> CompilerState a m Bool Source #
csCheckValueInit :: CompilerContext c m s a => [c] -> TypeInstance -> ExpressionType -> CompilerState a m () Source #
csCheckVariableInit :: CompilerContext c m s a => [UsedVariable c] -> 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 #
csDelegateArgs :: CompilerContext c m s a => CompilerState a m (Positional (Maybe (CallArgLabel c), VariableName)) Source #
csExprLookup :: CompilerContext c m s a => [c] -> MacroName -> 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 => JumpType -> CompilerState a m (CleanupBlock c 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 #
csGetTestsOnly :: CompilerContext c m s a => CompilerState a m Bool Source #
csGetTypeFunction :: CompilerContext c m s a => [c] -> Maybe GeneralInstance -> FunctionName -> CompilerState a m (ScopedFunction c) Source #
csGetVariable :: CompilerContext c m s a => UsedVariable c -> CompilerState a m (VariableValue c) Source #
csInheritDeferred :: CompilerContext c m s a => DeferVariable c -> CompilerState a m () Source #
csInheritStatic :: CompilerContext c m s a => [a] -> CompilerState a m () Source #
csInheritUsed :: 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 => a -> CompilerState a m () Source #
csRegisterReturn :: CompilerContext c m s a => [c] -> Maybe ExpressionType -> CompilerState a m () Source #
csReleaseExprMacro :: CompilerContext c m s a => [c] -> MacroName -> CompilerState a m () Source #
csReserveExprMacro :: CompilerContext c m s a => [c] -> MacroName -> 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 #
csSelfType :: CompilerContext c m s a => CompilerState a m TypeInstance Source #
csSetDeferred :: CompilerContext c m s a => UsedVariable c -> CompilerState a m () Source #
csSetHidden :: CompilerContext c m s a => UsedVariable c -> CompilerState a m () Source #
csSetJumpType :: CompilerContext c m s a => [c] -> JumpType -> CompilerState a m () Source #
csSetNoTrace :: CompilerContext c m s a => Bool -> CompilerState a m () Source #
csSetReadOnly :: CompilerContext c m s a => UsedVariable c -> CompilerState a m () Source #
csStartCleanup :: CompilerContext c m s a => [c] -> 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 #
emptyCleanupBlock :: Monoid s => CleanupBlock c s Source #
followDeferred :: DeferVariable c -> DeferVariable c -> DeferVariable c Source #
getCleanContext :: CompilerContext c m s a => CompilerState a m a Source #
removeDeferred :: VariableName -> DeferVariable c -> DeferVariable c Source #
runDataCompiler :: CompilerContext c m s a => CompilerState a m b -> a -> m (CompiledData s) Source #